'From Squeak3.2gamma of 17 March 2002 [latest update: #4857] on 7 July 2002 at 2:22:13 pm'! "Change Set: SSP Date: 7 July 2002 Author: Federico Gregorio Stilman SSP (Smalltalk Server Pages) support. Enables embedding Smalltalk code in HTML and other documents too."! Smalltalk renameClassNamed: #SSPTemplate as: #STTTemplate! Object subclass: #STTTemplate instanceVariableNames: 'sttCode ' classVariableNames: '' poolDictionaries: '' category: 'STT-Core'! !STTTemplate methodsFor: 'private' stamp: 'FGS 7/7/2002 14:01'! asSmalltalkCode "Returns the equivalent version of the receiver as Smalltalk code" | sttOpenIndex sttCloseIndex lastIndex sttCodeIndex stream | stream _ String new writeStream. stream nextPutAll: '| out | out _ String new writeStream.'; cr. lastIndex _ 1. [ (sttOpenIndex _ self sttCode indexOfSubCollection: '<%' startingAt: lastIndex) > 0] whileTrue: [ stream nextPutAll: 'out nextPutAll: '''; nextPutAll: (self sttCode copyFrom: lastIndex to: sttOpenIndex - 1); nextPutAll: '''.'; cr. sttCloseIndex _ self sttCode indexOfSubCollection: '%>' startingAt: sttOpenIndex ifAbsent: [ ^ self error: 'Missing closing tag' ]. sttCodeIndex _ sttOpenIndex + 2. (sttCode at: sttOpenIndex + 2) = $= ifTrue: [ stream nextPutAll: 'out nextPutAll: ('. sttCodeIndex _ sttCodeIndex + 1. ]. stream nextPutAll: (sttCode copyFrom: sttCodeIndex to: sttCloseIndex - 1). (sttCode at: sttOpenIndex + 2) = $= ifTrue: [ stream nextPutAll: ') asString.' ]. stream cr. lastIndex _ sttCloseIndex + 2. ]. stream nextPutAll: 'out nextPutAll: '''; nextPutAll: (self sttCode copyFrom: lastIndex to: sttCode size); nextPutAll: '''.'; cr; nextPutAll: '^ out contents'; cr. ^ stream contents ! ! !STTTemplate methodsFor: 'private' stamp: 'FGS 7/7/2002 03:30'! writeOutputCodeFor: aString on: aStream aStream nextPutAll: 'out nextPutAll: '''; nextPutAll: aString; nextPutAll: '''.'; cr.! ! !STTTemplate methodsFor: 'evaluating' stamp: 'FGS 7/7/2002 02:37'! evaluateOn: anObject "Evaluates the receiver within the context of anObject" ^ Compiler evaluate: self asSmalltalkCode for: anObject logged: false. ! ! !STTTemplate methodsFor: 'accessing' stamp: 'FGS 7/7/2002 13:58'! sttCode ^ sttCode! ! !STTTemplate methodsFor: 'initializing' stamp: 'FGS 7/7/2002 14:11'! initializeOn: aString sttCode _ aString! ! !STTTemplate class methodsFor: 'unit testing' stamp: 'FGS 7/7/2002 14:06'! test | sttTest | sttTest _ '
<%= each %> | <%= each * 2 %> |
This paragraph was manually send out
'' ]. %> '. ^ (STTTemplate on: sttTest) evaluateOn: 1.! ! !STTTemplate class methodsFor: 'instance creation' stamp: 'FGS 7/6/2002 17:25'! on: aString ^ super new initializeOn: aString.! ! STTTemplate removeSelector: #sspCode!