Squeak Server Pages

Stephen Pair squeak-dev at lists.squeakfoundation.org
Mon Oct 7 13:46:27 UTC 2002


This is a multi-part message in MIME format.

------=_NextPart_000_0057_01C26DE6.68C9DA80
Content-Type: text/plain;
	charset="us-ascii"
Content-Transfer-Encoding: 7bit

Yes, SSP works fine on Squeak 3.2.  It's probably a download issue.  You
need to make sure that the downloaded change set has not been munged or
contains any XML doctype header stuff.  Sometimes browsers like to
insert LFs when it thinks it has a text document...you could also change
Squeak's FileStream>>concreteStream method to use CrLfFileStream to work
around that issue.  Anyway, I was able to download, file in and use SSP
in Squeak 3.2 with no problems after cleaning up the file.

I've attached a clean change set to this message to make it
simpler...I've also uploaded a zipped version to the swiki (to work
around the file conversion issues).

- Stephen 

> -----Original Message-----
> From: squeak-dev-admin at lists.squeakfoundation.org 
> [mailto:squeak-dev-admin at lists.squeakfoundation.org] On 
> Behalf Of Daniel Joyce
> Sent: Monday, October 07, 2002 1:02 AM
> To: squeak-dev at lists.squeakfoundation.org
> Subject: Squeak Server Pages
> 
> 
> Heya,
> 
> I just stumbled across the SPP stuff on the squeak swiki, the last 
> update for it was 2.9 though.
> 
> There is also another Squeak Template pages system, but it 
> doesn't seem 
> to be as clean or easy to use as SPP is. Supposedly, it's 
> used for good 
> chunks of Swiki.net
> 
> Has it been ported forward to 3.2 yet? Is Stephen Pair still on this 
> list?
> 
> When I try and file it into a recent version, I get a traceback.
> 
> -Daniel
> 
> 

------=_NextPart_000_0057_01C26DE6.68C9DA80
Content-Type: application/octet-stream;
	name="ssp.cs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="ssp.cs"

'From Squeak2.9alpha of 13 June 2000 [latest update: #3193] on 23 March =
2001 at 4:06:51 pm'!=0D"Change Set:		kom-SSP=0DDate:			23 March =
2001=0DAuthor:			Stephen Pair, Bolot Kerimbaev=0D=0DThis is a port of =
Stephen Pair's SSP to kom47, with adjustment to the realities of Squeak =
2.9 alpha, 3.0, and 3.1 alpha -- parsing changed!! Below is the original =
preamble:=0D=0DThis change set enables servlet style methods to be =
written in the class browser.  I named it SSP because of it's likeness =
to JSP, PSP, etc.  However, it's not exactly like those schemes, in that =
it has nothing (necessarily) to do with web serving and the like.  SSP =
methods write the contents of their source onto a stream.  Smalltalk =
code segments (delinieated with <% and %>) can be embedded into this =
text.  Additionally, embedding Smalltalk code between <%=3D and %>, will =
force the compiler to send #sspStreamOn: to the result of evaluating the =
enclosed expression.=0D=0DThe following is an example:=0D=0D--- snip =
---=0DserveletExampleOn: strm=0D<ssp on: strm>=0D=0DThis is an example =
servelet method.  I can embed code in this=0Dstring as follows:  <%=3D =
(1 + 1) printString %>.=0D=0D--- snip ---=0D=0DTo illustrate, this =
change set includes an example class, SSPPerson.  Evaluate:=0D=0D	=
SSPPerson example=0D=0Dand inspect the result.  Reading through the =
code, you will see the example ssp method.  SSP methods write their =
result onto a stream.  Streams are used to ensure the highest possible =
flexibility and speed.  Also, the <ssp on: strm> pragma indicates that =
the special SSPParser should be used instead of the regular parser.  It =
also indicates that the parameter 'strm' is to be used as the target for =
writing.  You must also have two carriage returns following the <ssp on: =
strm> pragma (to separate what is intended to be written onto the stream =
from the method header).=0D=0DAnother variation of the method begins =
with a pragma of <ssp blockOn: strm> and will answer a monadic valuable =
block that takes a stream as it's argument.  These methods do not =
require the target stream to be passed as an argument.  Additionally, =
'strm' can be any identifier and can be referenced in the body of the =
method.=0D=0DA couple of escape sequences are provided for convenience.  =
First, a '\' at the end of a line will skip the carriage return =
character when writing onto the target stream.  Second, a '\]' will =
result in a single ']' being written onto the target stream.  =
=0D=0DWithin a block, you may include an <ssp> pragma to force SSP =
treatment of the contents of the block.  A single space should follow =
<ssp>.  Normally, blocks within an SSP method will be treated as normal =
Smalltalk.  The following is an illustration:=0D=0D--- snip =
---=0DservletExample: strm=0D<ssp on: strm>=0D=0DThis person <%=0D	=
address ifNil: [<ssp> does not] ifNotNil: [<ssp> does]=0D%> have an =
address.=0D--- snip ---=0D=0DEnjoy!!"!=0D=0DError subclass: =
#ParserRetry=0D	instanceVariableNames: 'retryClass '=0D	=
classVariableNames: ''=0D	poolDictionaries: ''=0D	category: =
'System-Compiler'!=0DParser subclass: #SSPParser=0D	=
instanceVariableNames: 'tmpVarNode firstArgName startOfLastString =
outsideServelet streamVarNode type innerBlock '=0D	classVariableNames: =
''=0D	poolDictionaries: ''=0D	category: 'SSP'!=0D=0D!SSPParser =
commentStamp: '<historical>' prior: 0!=0DMain comment stating the =
purpose of this class and relevant relationship to other =
classes.=0D=0DPossible useful expressions for doIt or =
printIt.=0D=0DStructure:=0D instVar1		type -- comment about the purpose =
of instVar1=0D instVar2		type -- comment about the purpose of =
instVar2=0D=0DAny further useful comments about the general approach of =
this implementation.!=0D=0DObject subclass: #SSPPerson=0D	=
instanceVariableNames: 'name address '=0D	classVariableNames: ''=0D	=
poolDictionaries: ''=0D	category: 'SSP'!=0D=0D!Object methodsFor: =
'squeak server pages' stamp: 'svp 5/3/2000 10:15'!=0DsspStreamOn: =
strm=0D=0D	self printOn: strm=0D! !=0D=0D=0D!BlockContext methodsFor: =
'squeak server pages' stamp: 'svp 5/3/2000 10:16'!=0DsspStreamOn: =
strm=0D	"Assume a one arg block"=0D=0D	^self value: strm! =
!=0D=0D=0D!Parser methodsFor: 'public access' stamp: 'bolot 3/23/2001 =
16:02'!=0Dparse: sourceStream class: class noPattern: noPattern context: =
ctxt notifying: req ifFail: aBlock =0D	"Answer a MethodNode for the =
argument, sourceStream, that is the root of =0D	a parse tree. Parsing is =
done with respect to the argument, class, to find =0D	instance, class, =
and pool variables; and with respect to the argument, =0D	ctxt, to find =
temporary variables. Errors in parsing are reported to the =0D	argument, =
req, if not nil; otherwise aBlock is evaluated. The argument =0D	=
noPattern is a Boolean that is true if the the sourceStream does not =0D	=
contain a method header (i.e., for DoIts)."=0D=0D	 | meth repeatNeeded =
myStream parser |=0D	(req notNil and: [RequestAlternateSyntaxSetting =
signal and: [(sourceStream isKindOf: FileStream) not]])=0D		ifTrue: =
[parser _ self as: DialectParser]=0D		ifFalse: [parser _ self].=0D	=
myStream _ sourceStream.=0D	[repeatNeeded _ false.=0D	parser init: =
myStream notifying: req failBlock: [^ aBlock value].=0D	doitFlag _ =
noPattern.=0D	failBlock_ aBlock.=0D	[meth _ parser method: noPattern =
context: ctxt=0D				encoder: (Encoder new init: class context: ctxt =
notifying: parser)] =0D		on: Exception =0D		do: =0D			[:ex |=0D			(ex =
isKindOf: ParserRemovedUnusedTemps)=0D				ifTrue: [repeatNeeded _ =
(requestor isKindOf: TextMorphEditor) not.=0D					myStream _ ReadStream =
on: requestor text string.=0D					ex resume]=0D				ifFalse: [=0D					(ex =
isKindOf: ParserRetry)=0D						ifTrue: [sourceStream reset.=0D							^ex =
retryClass new=0D								parse: sourceStream =0D								class: class =0D	=
							noPattern: noPattern =0D								context: ctxt =0D								=
notifying: req =0D								ifFail: aBlock]=0D						ifFalse: [ex signal =
"re-raise the exception if not handled"]]].=0D	repeatNeeded] =
whileTrue.=0D	encoder _ failBlock _ requestor _ parseNode _ nil. "break =
cycles & mitigate refct overflow"=0D	^ meth! !=0D=0D!Parser methodsFor: =
'pragmas' stamp: 'svp 3/17/2000 10:29'!=0Dpragma=0D	| n |=0D	(self =
matchToken: #<) ifFalse: [^ 0].=0D	n _ self pragmaDeclaration.=0D	(self =
matchToken: #>) ifFalse: [^ self expected: '>'].=0D	^ n! !=0D=0D!Parser =
methodsFor: 'pragmas' stamp: 'svp 3/20/2000 =
18:37'!=0DpragmaDeclaration=0D=0D	(here =3D 'primitive:') ifTrue: [ =
^self primitiveDeclarations ].=0D	(self matchToken: 'ssp') ifTrue: [ =
^self sspDeclaration ].=0D	(here =3D 'apicall:') ifTrue: [ ^self =
externalFunctionDeclaration ].=0D	^self expected: 'pragma =
declaration'=0D! !=0D=0D!Parser methodsFor: 'pragmas' stamp: 'svp =
3/17/2000 10:32'!=0Dprimitive=0D	=0D	^self pragma! !=0D=0D!Parser =
methodsFor: 'pragmas' stamp: 'svp 3/17/2000 =
10:30'!=0DsspDeclaration=0D=0D	ParserRetry new=0D		retryClass: =
SSPParser;=0D		signal=0D! !=0D=0D=0D!ParserRetry methodsFor: 'accessing' =
stamp: 'svp 3/17/2000 10:27'!=0DretryClass=0D=0D	^retryClass! =
!=0D=0D!ParserRetry methodsFor: 'accessing' stamp: 'svp 3/17/2000 =
10:27'!=0DretryClass: aParserClass=0D=0D	retryClass _ aParserClass! =
!=0D=0D=0D!SSPParser methodsFor: 'accessing' stamp: 'svp 3/20/2000 =
19:21'!=0DstreamVarNode=0D=0D	^streamVarNode! !=0D=0D!SSPParser =
methodsFor: 'accessing' stamp: 'svp 3/29/2000 11:31'!=0Dtype=0D	=
"Indicates whether the method should return a string, or append to a=0D	=
stream"=0D=0D	^type! !=0D=0D!SSPParser methodsFor: 'expression types' =
stamp: 'svp 5/3/2000 12:31'!=0DaddBlockWrapper: stmts startPosition: =
start=0D=0D	| tmp |=0D	tmp _ BlockNode new=0D			arguments: (Array with: =
self streamVarNode)=0D			statements: stmts=0D			returns: false=0D			=
from: encoder.=0D=0D	^OrderedCollection new=0D		add: (ReturnNode new=0D		=
	expr: tmp=0D			encoder: encoder=0D			sourceRange: (start to: self =
endOfLastToken));=0D		yourself! !=0D=0D!SSPParser methodsFor: =
'expression types' stamp: 'svp 3/29/2000 14:09'!=0DaddStreamWrapper: =
stmts=0D	| tmp lastStmt mn |=0D=0D	tmp _ stmts asArray.=0D	lastStmt _ =
tmp last.=0D	mn _ MessageNode new=0D		receiver: lastStmt=0D		selector: =
#sspStreamOn:=0D		arguments: (Array with: self streamVarNode)=0D		=
precedence: 1=0D		from: encoder=0D		sourceRange: (startOfLastString to: =
startOfLastString).=0D	tmp at: tmp size put: mn.=0D	^tmp=0D=0D=0D	! =
!=0D=0D!SSPParser methodsFor: 'expression types' stamp: 'svp 3/20/2000 =
19:36'!=0DblockExpression=0D	" [ {:var} ( | statements) ] =3D> =
BlockNode."=0D=0D	| argNodes |=0D	argNodes _ OrderedCollection new.=0D	=
[self match: #colon=0D	"gather any arguments"]=0D		whileTrue: =0D			=
[argNodes addLast: (encoder autoBind: self argumentName)].=0D	(argNodes =
size > 0 & (hereType ~~ #rightBracket) and: [(self match: #verticalBar) =
not])=0D		ifTrue: [^self expected: 'Vertical bar'].=0D	self =
sspBlockPragmaDeclaration ifTrue: [=0D		self sspStatements: argNodes =
innerBlock: true.=0D	] ifFalse: [=0D		self statements: argNodes =
innerBlock: true.=0D	].=0D	(self match: #rightBracket)=0D		ifFalse: =
[^self expected: 'Period or right bracket'].=0D	argNodes do: [:arg | arg =
scope: -1] "Scope no longer active"! !=0D=0D!SSPParser methodsFor: =
'expression types' stamp: 'svp 3/20/2000 19:16'!=0DenclosingString=0D	| =
lit |=0D=0D	(hereType =3D=3D #string) ifFalse: [ ^false ].=0D	lit _ =
encoder encodeLiteral: here.=0D	parseNode _ MessageNode new=0D		=
receiver: self streamVarNode=0D		selector: #nextPutAll:=0D		arguments: =
(Array with: lit)=0D		precedence: 1=0D		from: encoder=0D		sourceRange: =
(startOfLastString to: self endOfLastToken).=0D	self advance.=0D	=
^true=0D=0D	! !=0D=0D!SSPParser methodsFor: 'expression types' stamp: =
'svp 3/29/2000 14:43'!=0DsspStatements: argNodes innerBlock: inner=0D=0D	=
| stmts returns more blockComment expEncString servStmts startOfText =
embed |=0D	stmts _ OrderedCollection new.=0D=0D	"give initial comment to =
block, since others trail statements"=0D	blockComment _ =
currentComment.=0D	embed _ false.=0D	currentComment _ nil.=0D	returns _ =
false.=0D	inner ifTrue: [=0D		more _ true=0D	] ifFalse: [=0D		(more _ =
self match: #xReturn) ifFalse: [ ^self expected: 'double return' ].=0D	=
].=0D	startOfText _ self startOfNextToken.=0D	(self stringInitNode) =
ifTrue: [ stmts addLast: parseNode ].=0D	expEncString _ true.=0D	=
servStmts _ OrderedCollection new.=0D	[ more ] whileTrue: [=0D		=
(expEncString and: [ self enclosingString ]) ifTrue: [=0D			servStmts =
isEmpty ifFalse: [=0D				embed ifTrue: [=0D					stmts addAll: (self =
addStreamWrapper: servStmts).=0D				] ifFalse: [=0D					stmts addAll: =
servStmts.		=0D				].=0D				servStmts _ OrderedCollection new.=0D			=
].=0D			(parseNode arguments first literalValue ~=3D '') ifTrue: [=0D				=
stmts addLast: parseNode.=0D			].=0D		] ifFalse: [=0D			(servStmts =
isEmpty and: [ self matchToken: #=3D ]) ifTrue: [=0D				embed _ true.=0D	=
		] ifFalse: [=0D				embed _ false.=0D			].=0D			(returns _ self match: =
#upArrow) ifTrue: [=0D				^self expected: 'Non-return expression'=0D			] =
ifFalse: [=0D				self expression ifTrue: [=0D					self addComment.=0D				=
	servStmts addLast: parseNode.=0D				] ifFalse: [=0D					self =
addComment.=0D=0D					stmts size =3D 0 ifTrue: [=0D						stmts addLast: =
(encoder encodeVariable:=0D							(inner ifTrue: ['nil'] ifFalse: =
['self']))=0D					].=0D				].=0D			].=0D		].=0D=0D		(self match: =
#startServelet) ifTrue: [=0D			more _ true.=0D			expEncString _ =
false.=0D		] ifFalse: [=0D			(self match: #endServelet) ifTrue: [ =0D				=
more _ true.=0D				expEncString _ true.=0D			] ifFalse: [=0D				more _ =
self match: #period.=0D			]=0D		].=0D=0D	].=0D	servStmts isEmpty =
ifFalse: [=0D		embed ifTrue: [=0D			stmts addAll: (self =
addStreamWrapper: servStmts).=0D		] ifFalse: [=0D			stmts addAll: =
servStmts.		=0D		].=0D	].=0D	(self stringReturnNode) ifTrue: [ stmts =
addLast: parseNode ].=0D	(inner not and: [self type =3D=3D #block]) =
ifTrue: [ =0D		stmts _ self addBlockWrapper: stmts startPosition: =
startOfText.=0D		returns _ true.=0D	].=0D	parseNode _ BlockNode new=0D			=
		arguments: argNodes=0D					statements: stmts=0D					returns: =
returns=0D					from: encoder.=0D	parseNode comment: blockComment.=0D=0D	=
^true! !=0D=0D!SSPParser methodsFor: 'expression types' stamp: 'svp =
3/20/2000 16:49'!=0Dstatements: argNodes innerBlock: inner=0D=0D	inner =
ifTrue: [ ^super statements: argNodes innerBlock: inner ].=0D	^self =
sspStatements: argNodes innerBlock: false! !=0D=0D!SSPParser methodsFor: =
'expression types' stamp: 'svp 3/21/2000 07:18'!=0DstringInitNode=0D=0D	=
(type =3D=3D #string) ifFalse: [ ^false ].=0D=0D	"Need to create an =
assignment node for 'tmp _ WriteStream on: ''' and=0D	assign that node =
to parseNode."=0D	self notYetImplemented.=0D	self halt.=0D! =
!=0D=0D!SSPParser methodsFor: 'expression types' stamp: 'svp 3/21/2000 =
07:18'!=0DstringReturnNode=0D=0D	(type =3D=3D #string) ifFalse: [ ^false =
].=0D=0D	"Need to create a return node for '^tmp contents' and=0D	assign =
that node to parseNode."=0D	self notYetImplemented.=0D	self halt.! =
!=0D=0D!SSPParser methodsFor: 'pragmas' stamp: 'svp 3/17/2000 =
10:31'!=0DexternalFunctionDeclaration=0D=0D	ParserRetry new=0D		=
retryClass: Parser;=0D		signal=0D! !=0D=0D!SSPParser methodsFor: =
'pragmas' stamp: 'svp 3/14/2000 19:56'!=0Dpragma=0D	| n |=0D	(self =
matchToken: #<) ifFalse: [^ 0].=0D	n _ self pragmaDeclaration.=0D	(self =
matchToken: #>) ifFalse: [^ self expected: '>'].=0D	^ n! =
!=0D=0D!SSPParser methodsFor: 'pragmas' stamp: 'svp 3/20/2000 =
13:09'!=0DpragmaDeclaration=0D=0D	(self matchToken: 'primitive:') =
ifTrue: [ ^self primitiveDeclaration ].=0D	(self matchToken: 'ssp') =
ifTrue: [ ^self sspDeclaration ].=0D	^self =
externalFunctionDeclaration.=0D! !=0D=0D!SSPParser methodsFor: 'pragmas' =
stamp: 'svp 3/14/2000 20:03'!=0Dprimitive=0D=0D	^self pragma! =
!=0D=0D!SSPParser methodsFor: 'pragmas' stamp: 'svp 3/17/2000 =
10:31'!=0DprimitiveDeclaration=0D=0D	ParserRetry new=0D		retryClass: =
Parser;=0D		signal=0D! !=0D=0D!SSPParser methodsFor: 'pragmas' stamp: =
'svp 3/20/2000 21:02'!=0DsspBlockPragmaDeclaration=0D=0D	| gotSpace |=0D	=
(self matchToken: #<) ifFalse: [ ^false ].=0D	outsideServelet _ true.=0D	=
innerBlock _ true.=0D	gotSpace _ (self step =3D $ ).=0D	(self =
matchToken: 'ssp') ifFalse: [ ^self expected: 'ssp' ].=0D	(self =
matchToken: #>) ifFalse: [ ^self expected: '>' ].=0D	gotSpace ifFalse: [ =
^self expected: 'space' ].=0D	^true=0D! !=0D=0D!SSPParser methodsFor: =
'pragmas' stamp: 'svp 3/29/2000 13:30'!=0DsspDeclaration=0D=0D	| =
varStart varEnd varName |=0D	(self matchToken: #blockOn:) ifTrue: [ =0D		=
type _ #block. =0D	] ifFalse: [=0D		(self matchToken: #on:) ifTrue: [=0D	=
		type _ #stream.=0D		] ifFalse: [=0D			^0=0D		]=0D	].=0D=0D	(hereType =
=3D=3D #word) ifFalse: [ ^self expected: 'variable name' ].=0D	varStart =
_ self startOfNextToken + requestorOffset.=0D	varName _ here =
asString.=0D	self advance.=0D	varEnd _ self endOfLastToken + =
requestorOffset.=0D=0D	(type =3D=3D #stream) ifTrue: [=0D		streamVarNode =
_ encoder =0D			encodeVariable: varName=0D			ifUnknown: [ self =
correctVariable: varName interval: (varStart to: varEnd) ].=0D	] =
ifFalse: [=0D		streamVarNode _ encoder bindTemp: varName.=0D		=
streamVarNode nowHasDef.=0D	].=0D	^0=0D=0D! !=0D=0D!SSPParser =
methodsFor: 'multi-character scans' stamp: 'svp 4/21/2000 =
12:08'!=0DliteralString=0D=0D	startOfLastString _ self =
startOfNextToken.=0D	buffer reset.=0D	[ ((hereChar =3D 30 asCharacter) =
and: [ source atEnd ]) not and: [=0D		((hereChar =3D $<) and: [ =
aheadChar =3D $% ]) not and: [=0D			innerBlock not or: [ hereChar ~=3D =
$] ]=0D		]=0D	]] whileTrue: [=0D		(hereChar =3D $\) ifTrue: [=0D			=
(aheadChar =3D Character cr) ifTrue: [ =0D				" Enable line continuation =
"=0D				self step; step.=0D			].=0D			(aheadChar =3D $]) ifTrue: [=0D				=
self step.=0D				buffer nextPut: self step.=0D			].=0D		] ifFalse: [=0D		=
	buffer nextPut: self step=0D		]=0D	].=0D=0D	outsideServelet _ false.=0D	=
token _ buffer contents.=0D	tokenType _ #string.=0D=0D! =
!=0D=0D!SSPParser methodsFor: 'multi-character scans' stamp: 'svp =
3/20/2000 19:27'!=0DxEndServelet=0D=0D	(aheadChar =3D 62 asCharacter) =
ifTrue: [=0D		self step; step.=0D		outsideServelet _ true.=0D		token _ =
#%>.=0D		tokenType _ #endServelet.=0D	] ifFalse: [=0D		self xBinary.=0D	=
].! !=0D=0D!SSPParser methodsFor: 'multi-character scans' stamp: 'svp =
3/16/2000 18:20'!=0DxReturn=0D=0D	(aheadChar =3D 13 asCharacter) ifTrue: =
[=0D		self step; step.=0D		outsideServelet _ true.=0D		token _ =
#return.=0D		tokenType _#xReturn.=0D	] ifFalse: [=0D		self step.=0D		=
self scanToken=0D	].=0D! !=0D=0D!SSPParser methodsFor: 'multi-character =
scans' stamp: 'svp 3/20/2000 19:27'!=0DxStartServelet=0D=0D	(aheadChar =
=3D 37 asCharacter) ifTrue: [=0D		self step; step.=0D		outsideServelet _ =
false.=0D		token _ #<%.=0D		tokenType _ #startServelet.=0D	] ifFalse: =
[=0D		self xBinary.=0D	].! !=0D=0D!SSPParser methodsFor: =
'initialize-release' stamp: 'svp 3/20/2000 19:57'!=0DinitScanner=0D=0D	=
buffer _ WriteStream on: (String new: 40).=0D	typeTable _ TypeTable =
copy.=0D	typeTable at: 13 put: #xReturn.=0D	typeTable at: 60 put: =
#xStartServelet.=0D	typeTable at: 37 put: #xEndServelet.=0D	=
outsideServelet _ false.=0D	innerBlock _ false.=0D	type _ #string.! =
!=0D=0D!SSPParser methodsFor: 'scanning' stamp: 'svp 3/16/2000 =
18:18'!=0DscanToken=0D=0D	^outsideServelet ifTrue: [ =0D		self =
literalString.=0D		token =0D	] ifFalse: [=0D		super scanToken=0D	]=0D! =
!=0D=0D=0D!SSPPerson methodsFor: 'accessing' stamp: 'svp 3/17/2000 =
10:52'!=0Daddress=0D=0D	^address! !=0D=0D!SSPPerson methodsFor: =
'accessing' stamp: 'svp 3/17/2000 10:55'!=0Daddress: aString=0D=0D	=
address _ aString! !=0D=0D!SSPPerson methodsFor: 'accessing' stamp: 'svp =
3/17/2000 10:52'!=0Dname=0D=0D	^name! !=0D=0D!SSPPerson methodsFor: =
'accessing' stamp: 'svp 3/17/2000 10:55'!=0Dname: aString=0D=0D	name _ =
aString! !=0D=0D!SSPPerson methodsFor: 'servelets' stamp: 'svp 3/21/2000 =
15:21'!=0DformattedNameAndAddress=0D=0D	| tmp |=0D	tmp _ WriteStream on: =
''.=0D	self formattedNameAndAddressOn: tmp.=0D	^tmp contents! =
!=0D=0D!SSPPerson methodsFor: 'servelets' stamp: 'svp 5/3/2000 =
12:32'!=0DformattedNameAndAddressOn: strm=0D<ssp on: strm>=0D=0DA =
Person:=0D	Name: <%=3D name %>=0D	Address: <%=3D address %>! =
!=0D=0D=0D!SSPPerson class methodsFor: 'example' stamp: 'svp 3/17/2000 =
10:54'!=0Dexample=0D	| tmp |=0D	"  SSPPerson example  "=0D=0D	tmp _ self =
new=0D		name: 'George P. Burdell';=0D		address: '123 Jones Street';=0D		=
yourself.=0D=0D	^tmp formattedNameAndAddress=0D		! !=0D=0D=0D!String =
methodsFor: 'squeak server pages' stamp: 'svp 5/3/2000 =
10:17'!=0DsspStreamOn: strm=0D=0D	strm nextPutAll: self! =
!=0D=0D=0D!UndefinedObject methodsFor: 'squeak server pages' stamp: 'svp =
5/3/2000 10:17'!=0DsspStreamOn: strm! !=0D
------=_NextPart_000_0057_01C26DE6.68C9DA80--




More information about the Squeak-dev mailing list