[Pkg] The Trunk: 51Deprecated-nice.25.mcz

commits at source.squeak.org commits at source.squeak.org
Wed May 4 22:10:42 UTC 2016


Nicolas Cellier uploaded a new version of 51Deprecated to project The Trunk:
http://source.squeak.org/trunk/51Deprecated-nice.25.mcz

==================== Summary ====================

Name: 51Deprecated-nice.25
Author: nice
Time: 5 May 2016, 12:10:16.185159 am
UUID: 9be9d957-c07f-4465-8433-e527f464f910
Ancestors: 51Deprecated-mt.24

Deprecate HtmlFileStream since its superclass is deprecated.

Thus also deprecate StandardFileStream>>asHtml which has no sender in trunk.

=============== Diff against 51Deprecated-mt.24 ===============

Item was added:
+ CrLfFileStream subclass: #HtmlFileStream
+ 	instanceVariableNames: 'prevPreamble'
+ 	classVariableNames: 'TabThing'
+ 	poolDictionaries: ''
+ 	category: '51Deprecated-Files-Kernel'!
+ 
+ !HtmlFileStream commentStamp: 'mk 8/30/2005 15:10' prior: 0!
+ The Class apes StandardFileStream, but converts the text to HTML before putting it out (primarily intended for printOut).  It can be invoked with
+ 
+ 	((FileStream fileNamed: 'changes.html') asHtml) fileOutChanges
+ 
+ Use usual FileStream methods to put out text converted to
+ 	HTML fairly approximating that text  (for best looks, use 
+ 	method:, methodHeader:, methodBody:, for code);
+ 
+ verbatim: puts text out without conversion;
+ 
+ command: put out HTML items, such as <br>, supplying the brackets.
+ 
+ header: and trailer: put out an HTML wrapper (preamble and closing text)
+ 
+ nextPut does the actual conversion, nextPutAll: defers characters to nextPut.
+ 
+ The code is fairly dumb at present, doing a wooden straightforward conversion of the text without attempting to capture the style or fonts in which the original text was rendered.  Tabs are handled awkwardly, using &nbsp, so that probably only leading strings are working right.  Style sheets now permit us to do a much neater looking job if there is interest in improving the looks of things.
+ 
+ Example:
+ 	Perform
+ 		HtmlFileStream example1
+ 	and then navigate your browser to file 'example1.html'!

Item was added:
+ ----- Method: HtmlFileStream class>>example1 (in category 'examples') -----
+ example1
+ 	"This example shows how HtmlFileStream class can be used for generating HTML file."
+ 
+ 	| htmlFileStream |
+ 	htmlFileStream := HtmlFileStream newFrom: (FileStream fileNamed: 'example1.html').
+ 	htmlFileStream
+ 		header;
+ 		command: 'H1';
+ 		nextPutAll: 'Hello, world!!';
+ 		command: '/H1';
+ 		trailer;
+ 		close.!

Item was added:
+ ----- Method: HtmlFileStream class>>initialize (in category 'class initialization') -----
+ initialize   "HtmlFileStream initialize"
+ 	TabThing := '&nbsp;&nbsp;&nbsp;'
+ 
+ "I took Ted's suggestion to use &nbsp, which works far better for the HTML.  Style sheets provide an alternative, possibly better, solution since they permit finer-grain control of the HTML formatting, and thus would permit capturing the style in which text was originally rendered.  Internal tabbings would still get lost. 1/1/99 acg."!

Item was added:
+ ----- Method: HtmlFileStream class>>newFrom: (in category 'instance creation') -----
+ newFrom: aFileStream
+ 	"Answer an HtmlFileStream that is 'like' aFileStream.  As a side-effect, the surviving fileStream answered by this method replaces aFileStream on the finalization registry. 1/6/99 acg"
+ 
+ 	|inst|
+ 	inst := super newFrom: aFileStream.
+ 	StandardFileStream unregister: aFileStream.
+ 	HtmlFileStream register: inst.
+ 	inst detectLineEndConvention.
+ 	^inst
+ !

Item was added:
+ ----- Method: HtmlFileStream>>command: (in category 'HTML') -----
+ command: aString
+ 	"Append HTML commands directly without translation.  Caller should not include < or >.  Note that font change info comes through here!!  4/5/96 tk"
+ 
+ 	(aString includes: $<) ifTrue: [self error: 'Do not put < or > in arg'].
+ 		"We do the wrapping with <> here!!  Don't put it in aString."
+ 	^ self verbatim: '<', aString, '>'!

Item was added:
+ ----- Method: HtmlFileStream>>copyMethodChunkFrom: (in category 'fileIn/Out') -----
+ copyMethodChunkFrom: aStream
+ 	"Overridden to bolden the first line (presumably a method header)"
+ 	| terminator code firstLine |
+ 	terminator := $!!.
+ 	aStream skipSeparators.
+ 	code := aStream upTo: terminator.
+ 	firstLine := code copyUpTo: Character cr.
+ 	firstLine size = code size
+ 		ifTrue: [self nextPutAll: code]
+ 		ifFalse: [self command: 'b'; nextPutAll: firstLine; command: '/b'.
+ 				self nextPutAll: (code copyFrom: firstLine size + 1 to: code size)].
+ 	self nextPut: terminator.
+ 	[aStream peekFor: terminator] whileTrue:   "case of imbedded (doubled) terminators"
+ 			[self nextPut: terminator;
+ 				nextPutAll: (aStream upTo: terminator);
+ 				nextPut: terminator]!

Item was added:
+ ----- Method: HtmlFileStream>>header (in category 'read, write, position') -----
+ header
+ 	"append the HTML header.  Be sure to call trailer after you put out the data.
+ 	4/4/96 tk"
+ 	| cr |
+ 	cr := String with: Character cr.
+ 	self command: 'HTML'; verbatim: cr.
+ 	self command: 'HEAD'; verbatim: cr.
+ 	self command: 'TITLE'.
+ 	self nextPutAll: '"', self name, '"'.
+ 	self command: '/TITLE'; verbatim: cr.
+ 	self command: '/HEAD'; verbatim: cr.
+ 	self command: 'BODY'; verbatim: cr.
+ !

Item was added:
+ ----- Method: HtmlFileStream>>nextChunk (in category 'fileIn/Out') -----
+ nextChunk
+ 	"Answer the contents of the receiver, up to the next terminator character (!!).  Imbedded terminators are doubled.  Undo and strip out all Html stuff in the stream and convert the characters back.  4/12/96 tk"
+ 	| out char did rest |
+ 	self skipSeparators.	"Absorb <...><...> also"
+ 	out := WriteStream on: (String new: 500).
+ 	[self atEnd] whileFalse: [
+ 		self peek = $< ifTrue: [self unCommand].	"Absorb <...><...>"
+ 		(char := self next) = $&
+ 			ifTrue: [
+ 				rest := self upTo: $;.
+ 				did := out position.
+ 				rest = 'lt' ifTrue: [out nextPut: $<].
+ 				rest = 'gt' ifTrue: [out nextPut: $>].
+ 				rest = 'amp' ifTrue: [out nextPut: $&].
+ 				did = out position ifTrue: [
+ 					self error: 'new HTML char encoding'.
+ 					"Please add it to this code"]]
+ 			ifFalse: [char = $!!	"terminator"
+ 				ifTrue: [
+ 					self peek = $!! ifFalse: [^ out contents].
+ 					out nextPut: self next]	"pass on one $!!"
+ 				ifFalse: [char asciiValue = 9
+ 							ifTrue: [self next; next; next; next "TabThing"].
+ 						out nextPut: char]]
+ 		].
+ 	^ out contents!

Item was added:
+ ----- Method: HtmlFileStream>>nextPut: (in category 'read, write, position') -----
+ nextPut: char
+ 	"Put a character on the file, but translate it first. 4/6/96 tk 1/1/98 acg"
+ 	char = $< ifTrue: [^ super nextPutAll: '&lt;'].
+ 	char = $> ifTrue: [^ super nextPutAll: '&gt;'].
+ 	char = $& ifTrue: [^ super nextPutAll: '&amp;'].
+ 	char asciiValue = 13 "return" 
+ 		ifTrue: [self command: 'br'].
+ 	char = $	"tab" 
+ 		ifTrue: [self verbatim: TabThing. ^super nextPut: char].
+ 	^ super nextPut: char!

Item was added:
+ ----- Method: HtmlFileStream>>nextPutAll: (in category 'read, write, position') -----
+ nextPutAll: aString
+ 	"Write the whole string, translating as we go. 4/6/96 tk"
+ 	"Slow, but faster than using aString asHtml?"
+ 
+ 	^aString do: [:each | self nextPut: each].!

Item was added:
+ ----- Method: HtmlFileStream>>skipSeparators (in category 'fileIn/Out') -----
+ skipSeparators
+ 	"Bsides the normal spacers, also skip any <...>, html commands.
+ 	4/12/96 tk"
+ 	| did |
+ 	[did := self position.
+ 		super skipSeparators.
+ 		self unCommand.	"Absorb <...><...>"
+ 		did = self position] whileFalse.	"until no change"
+ !

Item was added:
+ ----- Method: HtmlFileStream>>trailer (in category 'read, write, position') -----
+ trailer
+ 	"append the HTML trailer.  Call this just before file close.
+ 	4/4/96 tk"
+ 	| cr |
+ 	cr := String with: Character cr.
+ 	self command: '/BODY'; verbatim: cr.
+ 	self command: '/HTML'; verbatim: cr.
+ !

Item was added:
+ ----- Method: HtmlFileStream>>verbatim: (in category 'read, write, position') -----
+ verbatim: aString
+ 	"Put out the string without HTML conversion. 1/1/99 acg"
+ 
+ 	super nextPutAll: aString
+ 
+ 	"'super verbatim:' in the 2.3beta draft didn't perform as expected -- the code was printed with conversion.  In a sense, that wouldn't make sense either -- we don't want strictly verbatim printing, just printing without the HTML conversion (that is, skipping around just the nextPut: and nextPutAll: for just this Class).  If there were intermediate conversions (say, CRLF!!), we would want those to happen as advertised -- perhaps we should use a differently named selector, perhaps something like nextPutWithoutHTMLConversion:, so that verbatim isn't overridden?"!

Item was added:
+ ----- Method: StandardFileStream>>asHtml (in category '*51Deprecated-Files-Kernel') -----
+ asHtml
+ 	"Convert me in to an HtmlFileStream. 4/11/96 tk"
+ 
+ 	^ self as: HtmlFileStream 
+ !



More information about the Packages mailing list