<br><br><div class="gmail_quote">On Tue, Feb 5, 2013 at 10:14 PM, Eliot Miranda <span dir="ltr">&lt;<a href="mailto:eliot.miranda@gmail.com" target="_blank">eliot.miranda@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Hi All,<div><br></div><div>    I had fun implementing a quasi-quote for Squeak today.  This is a convenient way of embedding substrings in format strings (a little like printf), and, because it uses a different quote character, a convenient way of embedding code form other languages in a string literal.</div>

<div><br></div><div>An example of the former usage is</div><div>    `hello [#cruel] world`</div><div>which evaluates to</div><div>    &#39;hello cruel world&#39;</div><div>And</div><div>    `Float pi is [Float pi]`</div>
<div>
evaluates to</div><div>    &#39;Float pi is 3.141592653589793&#39;</div><div><br></div><div>An example of the latter use is that one can write</div><div>    `printf(&quot;%s: %c\\n&quot;, &quot;a string&quot;, &#39;C&#39;);`</div>

<div>instead of</div><div>    &#39;printf(&quot;%s: %c\n&quot;, &quot;a string&quot;, &#39;&#39;C&#39;&#39;);&#39;</div><div><br></div><div>This last example shows a limitation; The use of \ to escape characters ($\ $[ and $`) in quasi-quote might not be such a good choice.</div>

<div><br></div><div><br></div><div>Anyway I thought I&#39;d put this in the in-box for people to play with and savage.  Please let me know what you think, both about the semantics and the implementation.  This is a quick hack and I&#39;m sure that there&#39;s plenty of scope for clean-up.</div>
</blockquote><div><br></div><div>And while I have it compiling, reporting errors, running and decompiling, I don&#39;t have it syntax highlighting yet.</div><div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

<div><br></div><div>cheers</div><div>Eliot<div><div class="h5"><br><br><div class="gmail_quote">On Tue, Feb 5, 2013 at 9:54 PM,  <span dir="ltr">&lt;<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>&gt;</span> wrote:<br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">A new version of Compiler was added to project The Inbox:<br>
<a href="http://source.squeak.org/inbox/Compiler.quasiquote-eem.248.mcz" target="_blank">http://source.squeak.org/inbox/Compiler.quasiquote-eem.248.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: Compiler.quasiquote-eem.248<br>
Author: eem<br>
Time: 5 February 2013, 9:54:20.317 pm<br>
UUID: ef044906-3339-48cc-856b-9b5172e3e81b<br>
Ancestors: Compiler-cwp.247<br>
<br>
Add a quasi-quote form that allows convenient embedding<br>
of substrings within a format string, and provides a<br>
convenient way of embedding literal strings within an<br>
alternative literal string whose string delimiter is different.<br>
<br>
e.g.<br>
        `hello [#cruel] world!`<br>
evaluates to<br>
        &#39;hello cruel world&#39;.<br>
<br>
        `S1[B1]...SN[BN]SN+1`<br>
<br>
is equivalent to<br>
        { &#39;S1&#39;. [B1] value. ... &#39;SN&#39;. [BN] value. &#39;SN+1&#39; } concatenateQuasiQuote<br>
where concatenateQuasiQuote sends asString to each<br>
element and answers the concatenation of those elements.<br>
<br>
however, single-statement blocks are inlined, so e.g. the<br>
above `hello [#cruel] world!` is compiled as<br>
        { &#39;hello &#39;. #cruel. &#39; world!&#39; } concatenateQuasiQuote<br>
<br>
See Tests.quasiquote-eem.188 for tests and examples.<br>
<br>
=============== Diff against Compiler-cwp.247 ===============<br>
<br>
Item was added:<br>
+ ----- Method: Array&gt;&gt;concatenateQuasiQuote (in category &#39;*Compiler-support&#39;) -----<br>
+ concatenateQuasiQuote<br>
+       &quot;This method is used in compilation of quasi-quote constructs.<br>
+       It MUST NOT be deleted or altered.&quot;<br>
+<br>
+       | s sz |<br>
+       sz := self size.<br>
+       s := WriteStream on: (String new: sz * 16).<br>
+       1 to: sz do:<br>
+               [:i| s nextPutAll: (self at: i) asString].<br>
+       ^s contents!<br>
<br>
Item was removed:<br>
- ----- Method: Decompiler&gt;&gt;checkForBlock:selector:arguments: (in category &#39;control&#39;) -----<br>
- checkForBlock: receiver selector: selector arguments: arguments<br>
-       selector == #blockCopy: ifTrue:<br>
-               [^self checkForBlockCopy: receiver].<br>
-       self assert: selector == #closureCopy:copiedValues:.<br>
-       ^self checkForClosureCopy: receiver arguments: arguments!<br>
<br>
Item was added:<br>
+ ----- Method: Decompiler&gt;&gt;checkForMacroMessage:selector:arguments: (in category &#39;control&#39;) -----<br>
+ checkForMacroMessage: rcvr selector: selector arguments: args<br>
+       ^       (selector == #concatenateQuasiQuote<br>
+                  and: [self checkForQuasiQuote: rcvr selector: selector arguments: args])<br>
+         or: [(#closureCopy:copiedValues: == selector<br>
+                  and: [self checkForClosureCopy: rcvr arguments: args])<br>
+         or: [#blockCopy: == selector<br>
+                 and: [self checkForBlockCopy: rcvr]]]!<br>
<br>
Item was added:<br>
+ ----- Method: Decompiler&gt;&gt;checkForQuasiQuote:selector:arguments: (in category &#39;control&#39;) -----<br>
+ checkForQuasiQuote: rcvr &quot;&lt;BraceNode&gt;&quot; selector: selector &quot;&lt;Symbol&gt;&quot; arguments: args &quot;&lt;Array&gt;&quot;<br>
+       stack addLast:<br>
+               ((MessageNode new<br>
+                               receiver: rcvr<br>
+                               selector: (SelectorNode new key: #concatenateQuasiQuote code: nil)<br>
+                               arguments: args<br>
+                               precedence: 1)<br>
+                       notePrintingSelector: #printQuasiQuoteOn:indent:;<br>
+                       yourself).<br>
+       ^true!<br>
<br>
Item was changed:<br>
  ----- Method: Decompiler&gt;&gt;send:super:numArgs: (in category &#39;instruction decoding&#39;) -----<br>
  send: selector super: superFlag numArgs: numArgs<br>
<br>
        | args rcvr selNode msgNode messages |<br>
        args := Array new: numArgs.<br>
        (numArgs to: 1 by: -1) do:<br>
                [:i | args at: i put: stack removeLast].<br>
        rcvr := stack removeLast.<br>
        superFlag ifTrue: [rcvr := constructor codeSuper].<br>
+       (self checkForMacroMessage: rcvr selector: selector arguments: args) ifFalse:<br>
-       ((#(blockCopy: closureCopy:copiedValues:) includes: selector)<br>
-         and: [self checkForBlock: rcvr selector: selector arguments: args]) ifFalse:<br>
                [selNode := constructor codeAnySelector: selector.<br>
                rcvr == CascadeFlag<br>
                        ifTrue:<br>
                                [&quot;May actually be a cascade or an ifNil: for value.&quot;<br>
                                self willJumpIfFalse<br>
                                        ifTrue: &quot;= generated by a case macro&quot;<br>
                                                [selector == #= ifTrue:<br>
                                                        [&quot; = signals a case statement...&quot;<br>
                                                        statements addLast: args first.<br>
                                                        stack addLast: rcvr. &quot;restore CascadeFlag&quot;<br>
                                                        ^ self].<br>
                                                selector == #== ifTrue:<br>
                                                        [&quot; == signals an ifNil: for value...&quot;<br>
                                                        stack removeLast; removeLast.<br>
                                                        rcvr := stack removeLast.<br>
                                                        stack addLast: IfNilFlag;<br>
                                                                addLast: (constructor<br>
                                                                        codeMessage: rcvr<br>
                                                                        selector: selNode<br>
                                                                        arguments: args).<br>
                                                        ^ self]]<br>
                                        ifFalse:<br>
                                                [(self willJumpIfTrue and: [selector == #==]) ifTrue:<br>
                                                        [&quot; == signals an ifNotNil: for value...&quot;<br>
                                                        stack removeLast; removeLast.<br>
                                                        rcvr := stack removeLast.<br>
                                                        stack addLast: IfNilFlag;<br>
                                                                addLast: (constructor<br>
                                                                        codeMessage: rcvr<br>
                                                                        selector: selNode<br>
                                                                        arguments: args).<br>
                                                        ^ self]].<br>
                                msgNode := constructor<br>
                                                                codeCascadedMessage: selNode<br>
                                                                arguments: args.<br>
                                stack last == CascadeFlag ifFalse:<br>
                                        [&quot;Last message of a cascade&quot;<br>
                                        statements addLast: msgNode.<br>
                                        messages := self popTo: stack removeLast.  &quot;Depth saved by first dup&quot;<br>
                                        msgNode := constructor<br>
                                                                        codeCascade: stack removeLast<br>
                                                                        messages: messages]]<br>
                        ifFalse:<br>
                                [msgNode := constructor<br>
                                                        codeMessage: rcvr<br>
                                                        selector: selNode<br>
                                                        arguments: args].<br>
                stack addLast: msgNode]!<br>
<br>
Item was changed:<br>
  ----- Method: MessageNode class&gt;&gt;initialize (in category &#39;class initialization&#39;) -----<br>
  initialize<br>
        &quot;MessageNode initialize&quot;<br>
        MacroSelectors :=<br>
                #(      ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:<br>
                        and: or:<br>
                        whileFalse: whileTrue: whileFalse whileTrue<br>
                        to:do: to:by:do:<br>
                        caseOf: caseOf:otherwise:<br>
                        ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:<br>
+                       repeat<br>
+                       nil &quot;space for concatenateQuasiQuote&quot; ).<br>
-                       repeat ).<br>
        MacroTransformers :=<br>
                #(      transformIfTrue: transformIfFalse: transformIfTrueIfFalse: transformIfFalseIfTrue:<br>
                        transformAnd: transformOr:<br>
                        transformWhile: transformWhile: transformWhile: transformWhile:<br>
                        transformToDo: transformToDo:<br>
                        transformCase: transformCase:<br>
                        transformIfNil: transformIfNil:  transformIfNilIfNotNil: transformIfNotNilIfNil:<br>
+                       transformRepeat:<br>
+                       nil &quot;space for concatenateQuasiQuote&quot; ).<br>
-                       transformRepeat: ).<br>
        MacroEmitters :=<br>
                #(      emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:<br>
                        emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:<br>
                        emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:<br>
                        emitCodeForWhile:encoder:value: emitCodeForWhile:encoder:value:<br>
                        emitCodeForWhile:encoder:value: emitCodeForWhile:encoder:value:<br>
                        emitCodeForToDo:encoder:value: emitCodeForToDo:encoder:value:<br>
                        emitCodeForCase:encoder:value: emitCodeForCase:encoder:value:<br>
                        emitCodeForIfNil:encoder:value: emitCodeForIfNil:encoder:value:<br>
                        emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:<br>
+                       emitCodeForRepeat:encoder:value:<br>
+                       nil &quot;space for concatenateQuasiQuote&quot;).<br>
-                       emitCodeForRepeat:encoder:value:).<br>
        MacroSizers :=<br>
                #(      sizeCodeForIf:value: sizeCodeForIf:value: sizeCodeForIf:value: sizeCodeForIf:value:<br>
                        sizeCodeForIf:value: sizeCodeForIf:value:<br>
                        sizeCodeForWhile:value: sizeCodeForWhile:value: sizeCodeForWhile:value: sizeCodeForWhile:value:<br>
                        sizeCodeForToDo:value: sizeCodeForToDo:value:<br>
                        sizeCodeForCase:value: sizeCodeForCase:value:<br>
                        sizeCodeForIfNil:value: sizeCodeForIfNil:value: sizeCodeForIf:value: sizeCodeForIf:value:<br>
+                       sizeCodeForRepeat:value:<br>
+                       nil &quot;space for concatenateQuasiQuote&quot;).<br>
-                       sizeCodeForRepeat:value:).<br>
        MacroPrinters :=<br>
                #(      printIfOn:indent: printIfOn:indent: printIfOn:indent: printIfOn:indent:<br>
                        printIfOn:indent: printIfOn:indent:<br>
                        printWhileOn:indent: printWhileOn:indent: printWhileOn:indent: printWhileOn:indent:<br>
                        printToDoOn:indent: printToDoOn:indent:<br>
                        printCaseOn:indent: printCaseOn:indent:<br>
                        printIfNil:indent: printIfNil:indent: printIfNilNotNil:indent: printIfNilNotNil:indent:<br>
+                       printRepeatOn:indent:<br>
+                       printQuasiQuoteOn:indent:)!<br>
-                       printRepeatOn:indent:)!<br>
<br>
Item was added:<br>
+ ----- Method: MessageNode&gt;&gt;notePrintingSelector: (in category &#39;macro transformations&#39;) -----<br>
+ notePrintingSelector: printingSelectorSymbol<br>
+       &quot;decompile&quot;<br>
+<br>
+       special := MacroPrinters indexOf: printingSelectorSymbol!<br>
<br>
Item was added:<br>
+ ----- Method: MessageNode&gt;&gt;printQuasiQuoteOn:indent: (in category &#39;printing&#39;) -----<br>
+ printQuasiQuoteOn: aStream indent: level<br>
+       aStream nextPut: $`.<br>
+       receiver elements do:<br>
+               [:parseNode|<br>
+               (parseNode isLiteralNode<br>
+                and: [parseNode key class == &#39;literal&#39; class])<br>
+                       ifTrue:<br>
+                               [parseNode key do:<br>
+                                       [:char|<br>
+                                       (&#39;`[\&#39; includes: char) ifTrue:<br>
+                                               [aStream nextPut: $\].<br>
+                                       aStream nextPut: char]]<br>
+                       ifFalse:<br>
+                               [(parseNode isMessageNode<br>
+                                 and: [parseNode selector key == #value<br>
+                                 and: [parseNode receiver isBlockNode]])<br>
+                                       ifTrue:<br>
+                                               [parseNode receiver printOn: aStream indent: 0]<br>
+                                       ifFalse:<br>
+                                               [aStream nextPut: $[.<br>
+                                                parseNode printOn: aStream indent: 0.<br>
+                                                aStream nextPut: $]]]].<br>
+       aStream nextPut: $`!<br>
<br>
Item was changed:<br>
  ----- Method: Parser&gt;&gt;advance (in category &#39;scanning&#39;) -----<br>
  advance<br>
        | this |<br>
        prevMark := hereMark.<br>
        prevEnd := hereEnd.<br>
        this := here.<br>
        here := token.<br>
        hereType := tokenType.<br>
        hereMark := mark.<br>
        hereEnd := source position - (aheadChar == DoItCharacter<br>
                ifTrue: [hereChar == DoItCharacter<br>
                        ifTrue: [0]<br>
                        ifFalse: [1]]<br>
                ifFalse: [2]).<br>
+       hereType ~~ #backQuote ifTrue:<br>
+               [self scanToken].<br>
-       self scanToken.<br>
        &quot;Transcript show: &#39;here: &#39;, here printString, &#39; mark: &#39;, hereMark printString, &#39; end: &#39;, hereEnd printString; cr.&quot;<br>
        ^this!<br>
<br>
Item was changed:<br>
  ----- Method: Parser&gt;&gt;expression (in category &#39;expression types&#39;) -----<br>
  expression<br>
<br>
+       (hereType == #word and: [tokenType == #leftArrow]) ifTrue:<br>
+               [^self assignment: self variable].<br>
+       hereType == #backQuote<br>
+               ifTrue: [self quasiQuoteExpression]<br>
+               ifFalse:<br>
+                       [hereType == #leftBrace<br>
+                               ifTrue: [self braceExpression]<br>
+                               ifFalse:<br>
+                                       [self primaryExpression ifFalse:<br>
+                                               [^false]]].<br>
+       (self messagePart: 3 repeat: true) ifTrue:<br>
+               [hereType == #semicolon ifTrue:<br>
+                       [self cascade]].<br>
+       ^true!<br>
-       (hereType == #word and: [tokenType == #leftArrow])<br>
-               ifTrue: [^ self assignment: self variable].<br>
-       hereType == #leftBrace<br>
-               ifTrue: [self braceExpression]<br>
-               ifFalse: [self primaryExpression ifFalse: [^ false]].<br>
-       (self messagePart: 3 repeat: true)<br>
-               ifTrue: [hereType == #semicolon ifTrue: [self cascade]].<br>
-       ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Parser&gt;&gt;nonQuasiQuoteExpression (in category &#39;expression types&#39;) -----<br>
+ nonQuasiQuoteExpression<br>
+<br>
+       (hereType == #word and: [tokenType == #leftArrow])<br>
+               ifTrue: [^ self assignment: self variable].<br>
+       hereType == #leftBrace<br>
+               ifTrue: [self braceExpression]<br>
+               ifFalse: [self primaryExpression ifFalse: [^ false]].<br>
+       (self messagePart: 3 repeat: true)<br>
+               ifTrue: [hereType == #semicolon ifTrue: [self cascade]].<br>
+       ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Parser&gt;&gt;quasiQuoteExpression (in category &#39;expression types&#39;) -----<br>
+ quasiQuoteExpression<br>
+       &quot;`quasi-quote`<br>
+               =&gt; { elements } concatenateQuasiQuote<br>
+                       =&gt; MessageNode receiver: BraceNode selector: #concatenateQuasiQuote.<br>
+<br>
+        The syntax of quasi-quote is<br>
+               quasi-quote := $` (characters | blockExpression) * $`<br>
+               characters := (unescapedCharacter | $\ escapedCharacter) *<br>
+<br>
+       The semantics of quasi-quote are that each blockExpression is evaluated<br>
+        left-to-right in the scope of the enclosing method or block.  The sequence<br>
+        of interspersed character sequences and expressions are concatenated<br>
+        left-to-right, sending asString to each element immediately prior to concatenation.<br>
+        The concatenation is then the result of the expression.  It is always a new string.<br>
+<br>
+        The implementation inlines single-statement blocks into the brace expression that<br>
+        comprises the receiver of concatenateQuasiQuote&quot;<br>
+<br>
+       | elements locations stringStream loc |<br>
+       elements := OrderedCollection new.<br>
+       locations := OrderedCollection new.<br>
+       stringStream := WriteStream on: (String new: 16).<br>
+       [loc := hereMark + requestorOffset.<br>
+        hereType == #doit ifTrue:<br>
+               [^self expected: &#39;back quote&#39;].<br>
+        hereType == #leftBracket<br>
+               ifTrue:<br>
+                       [self scanToken; advance.<br>
+                        parseNode := nil.<br>
+                        self blockExpression.<br>
+                        parseNode statements size = 1<br>
+                               ifTrue:<br>
+                                       [elements addLast: parseNode statements first]<br>
+                               ifFalse:<br>
+                                       [elements addLast: (MessageNode new<br>
+                                                                                       receiver: parseNode<br>
+                                                                                       selector: #value<br>
+                                                                                       arguments: #()<br>
+                                                                                       precedence: 1<br>
+                                                                                       from: encoder)].<br>
+                        source position: hereMark - 1.<br>
+                        [source peek ~~ $]] whileTrue:<br>
+                               [source position: source position - 1].<br>
+                        source next.<br>
+                        self step; step.<br>
+                        self setHereTypeForQuasiQuote.<br>
+                        locations addLast: loc]<br>
+               ifFalse:<br>
+                       [(self scanQuasiQuoteCharactersUsing: stringStream) ifNotNil:<br>
+                               [:lit|<br>
+                                elements addLast: lit.<br>
+                                locations addLast: loc]].<br>
+        hereType ~~ #backQuote] whileTrue.<br>
+       parseNode := MessageNode new<br>
+                                       receiver: (BraceNode new elements: elements sourceLocations: locations)<br>
+                                       selector: #concatenateQuasiQuote<br>
+                                       arguments: #()<br>
+                                       precedence: 1<br>
+                                       from: encoder.<br>
+       self scanToken; advance.<br>
+       ^true!<br>
<br>
Item was changed:<br>
+ ----- Method: Parser&gt;&gt;queriedUnusedTemporaries (in category &#39;temps&#39;) -----<br>
- ----- Method: Parser&gt;&gt;queriedUnusedTemporaries (in category &#39;accessing&#39;) -----<br>
  queriedUnusedTemporaries<br>
<br>
        queriedUnusedTemporaries ifNil:<br>
                [queriedUnusedTemporaries := Dictionary new].<br>
        ^queriedUnusedTemporaries!<br>
<br>
Item was added:<br>
+ ----- Method: Parser&gt;&gt;scanQuasiQuoteCharactersUsing: (in category &#39;scanning&#39;) -----<br>
+ scanQuasiQuoteCharactersUsing: stringStream<br>
+       &quot;Answer the next non-empty sequence of characters in a quasi-quote string, or nil, if none.&quot;<br>
+       stringStream reset.<br>
+       [hereChar ~~ $` and: [hereChar ~~ $[ and: [hereChar ~~ DoItCharacter]]] whileTrue:<br>
+               [hereChar == $\<br>
+                       ifTrue:<br>
+                               [stringStream nextPut: aheadChar. self step]<br>
+                       ifFalse:<br>
+                               [stringStream nextPut: hereChar].<br>
+                self step].<br>
+       self setHereTypeForQuasiQuote.<br>
+       ^stringStream position &gt; 0 ifTrue:<br>
+               [encoder encodeLiteral: stringStream contents]!<br>
<br>
Item was added:<br>
+ ----- Method: Parser&gt;&gt;setHereTypeForQuasiQuote (in category &#39;scanning&#39;) -----<br>
+ setHereTypeForQuasiQuote<br>
+       &quot;Set hereType appropriately based on hereChar.  Used only for quasi-quote parsing.&quot;<br>
+       hereChar == $`<br>
+               ifTrue:<br>
+                       [hereType := #backQuote.<br>
+                        self step]<br>
+               ifFalse:<br>
+                       [hereChar == $[<br>
+                               ifTrue:<br>
+                                       [hereType := #leftBracket.<br>
+                                        self step]<br>
+                               ifFalse:<br>
+                                       [hereChar == DoItCharacter ifTrue:<br>
+                                               [hereType := #doit]]]!<br>
<br>
Item was changed:<br>
+ ----- Method: Parser&gt;&gt;tempsMark (in category &#39;temps&#39;) -----<br>
- ----- Method: Parser&gt;&gt;tempsMark (in category &#39;accessing&#39;) -----<br>
  tempsMark<br>
        ^ tempsMark!<br>
<br>
Item was changed:<br>
+ ----- Method: Parser&gt;&gt;tempsMark: (in category &#39;temps&#39;) -----<br>
- ----- Method: Parser&gt;&gt;tempsMark: (in category &#39;accessing&#39;) -----<br>
  tempsMark: aNumber<br>
  tempsMark := aNumber!<br>
<br>
Item was changed:<br>
  ----- Method: Scanner class&gt;&gt;initializeTypeTable (in category &#39;initialization&#39;) -----<br>
  initializeTypeTable<br>
        &quot;self initializeTypeTable&quot;<br>
<br>
        | newTable |<br>
        newTable := Array new: 256 withAll: #xBinary. &quot;default&quot;<br>
        newTable atAll: #(9 10 12 13 32 ) put: #xDelimiter. &quot;tab lf ff cr space&quot;<br>
        newTable atAll: ($0 asciiValue to: $9 asciiValue) put: #xDigit.<br>
<br>
        1 to: 255<br>
                do: [:index |<br>
                        (Character value: index) isLetter<br>
                                ifTrue: [newTable at: index put: #xLetter]].<br>
<br>
        newTable at: $&quot; asciiValue put: #xDoubleQuote.<br>
        newTable at: $# asciiValue put: #xLitQuote.<br>
        newTable at: $$ asciiValue put: #xDollar.<br>
        newTable at: $&#39; asciiValue put: #xSingleQuote.<br>
+       newTable at: $` asciiValue put: #backQuote.<br>
        newTable at: $: asciiValue put: #xColon.<br>
        newTable at: $( asciiValue put: #leftParenthesis.<br>
        newTable at: $) asciiValue put: #rightParenthesis.<br>
        newTable at: $. asciiValue put: #period.<br>
        newTable at: $; asciiValue put: #semicolon.<br>
        newTable at: $[ asciiValue put: #leftBracket.<br>
        newTable at: $] asciiValue put: #rightBracket.<br>
        newTable at: ${ asciiValue put: #leftBrace.<br>
        newTable at: $} asciiValue put: #rightBrace.<br>
        newTable at: $^ asciiValue put: #upArrow.<br>
        newTable at: $_ asciiValue put: #xUnderscore.<br>
        newTable at: $| asciiValue put: #verticalBar.<br>
        TypeTable := newTable &quot;bon voyage!!&quot;!<br>
<br>
<br>
</blockquote></div><br><br clear="all"><div><br></div></div></div><span class="HOEnZb"><font color="#888888">-- <br>best,<div>Eliot</div>
</font></span></div>
</blockquote></div><br><br clear="all"><div><br></div>-- <br>best,<div>Eliot</div>