Hi Joe,<div><br></div><div>Thank you for asking interesting questions and staying involved. </div><div><br></div><div>One way to find this out for yourself is to run this code to step through what is happening (highlighting the two lines and hitting the PrintIt key combo):</div>

<div><div><font face="courier new, monospace">self halt. </font></div><div><font face="courier new, monospace">&#39;123%s456&#39; printf: (&#39;s&#39;).</font></div></div><div><br></div><div>You&#39;ll find that the class ByteString also now has a <font face="courier new, monospace">#printf:</font> method inherited from String class. So, the ByteString class knows how to convert itself to a FormatString if it sees a <font face="courier new, monospace">#printf:</font> method.</div>

<div><div><font face="courier new, monospace">printf: arguments</font></div><div><font face="courier new, monospace">        ^ self asFormatString printf: arguments</font></div></div><div><br>The &#39; * &#39; in <font face="courier new, monospace">*printf</font> method category name is a visual clue that a load has added it to the default String class.</div>

<div><br></div><div>- Darius</div><div>_______________<br><br><div class="gmail_quote">On Mon, Oct 8, 2012 at 3:13 PM, Joseph J Alotta <span dir="ltr">&lt;<a href="mailto:joseph.alotta@gmail.com" target="_blank">joseph.alotta@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">Greetings:<br>
<br>
I filed in the below code.  When I ask &#39;%6.2e&#39; what class it is, it replies ByteString.<br>
<br>
&#39;%6.2e&#39; class =&gt; ByteString<br>
<br>
When I send a ByteString the #printf, it somehow knows to look in the FormatString class for this<br>
method.<br></blockquote><div><br></div><div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<br>
&#39;%6.2e&#39; printf: 412.343434 =&gt; &#39;412.34&#39;<br>
<br>
My question is, where is the place in the below code where this gets redirected?  i.e., Where the<br>
printf method gets added to the ByteString path of available methods.<br>
<br>
<br>
Thanks for your help,<br>
<br>
Joe.<br>
<br>
<br>
<br>
<br>
<br>
<br>
Object subclass: #FormatDescriptor<br>
        instanceVariableNames: &#39;flush width precision&#39;<br>
        classVariableNames: &#39;Flags Operators&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!FormatDescriptor methodsFor: &#39;rendering&#39;!<br>
applyOperator: object<br>
        self subclassResponsibility! !<br>
<br>
!FormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;hjo 9/18/2011 00:31&#39;!<br>
render: object<br>
        | string |<br>
        string := self applyOperator: object.<br>
        self stringLength ~= 0<br>
                ifTrue: [ string := string copyFrom: 1 to: (self stringLength min: string size) ].<br>
        width == 0<br>
                ifTrue: [ ^ string ].<br>
        ^ (String new: width withAll: self padding)<br>
                copyReplaceFrom: (self startIndexOfCopyReplaceWithStringSize: string size)<br>
                to: (self stopIndexOfCopyReplaceWithStringSize: string size)<br>
                with: string! !<br>
<br>
!FormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;hjo 9/18/2011 00:31&#39;!<br>
startIndexOfCopyReplaceWithStringSize: anInteger<br>
<br>
        |start|<br>
        flush == #leftFlush ifTrue: [start := 1].<br>
        flush == #rightFlush ifTrue: [start := width - anInteger + 1].<br>
        ^(start max: 1)<br>
! !<br>
<br>
!FormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;hjo 9/18/2011 00:31&#39;!<br>
stopIndexOfCopyReplaceWithStringSize: anInteger<br>
<br>
        | stop |<br>
        flush == #leftFlush ifTrue: [stop := anInteger].<br>
        flush == #rightFlush ifTrue: [stop := width].<br>
        ^stop min: width! !<br>
<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
flush<br>
        ^ flush! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39; stamp: &#39;mir 6/6/2000 23:58&#39;!<br>
operator: char<br>
        | myself |<br>
        myself := (Smalltalk at: (Operators at: char)) newFrom: self.<br>
        myself setOperator: char.<br>
        ^ myself! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
padding<br>
        ^ Character space! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
precision<br>
        ^ precision! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
precision: anInteger<br>
        precision := anInteger! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
setOperator: char! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
stringLength<br>
        ^ precision isNil ifTrue: [0] ifFalse: [precision]! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
width<br>
        ^ width! !<br>
<br>
!FormatDescriptor methodsFor: &#39;private&#39;!<br>
width: anInteger<br>
        width := anInteger! !<br>
<br>
<br>
!FormatDescriptor methodsFor: &#39;initialize-release&#39;!<br>
initialize<br>
        flush := #rightFlush.<br>
        width := 0! !<br>
<br>
<br>
!FormatDescriptor methodsFor: &#39;scanning&#39;!<br>
leftFlush<br>
        flush := #leftFlush! !<br>
<br>
!FormatDescriptor methodsFor: &#39;scanning&#39;!<br>
radix<br>
        ^ (NumberFormatDescriptor newFrom: self) radix! !<br>
<br>
!FormatDescriptor methodsFor: &#39;scanning&#39;!<br>
rightFlush<br>
        flush := #rightFlush! !<br>
<br>
!FormatDescriptor methodsFor: &#39;scanning&#39;!<br>
space<br>
        ^ (NumberFormatDescriptor newFrom: self) space! !<br>
<br>
!FormatDescriptor methodsFor: &#39;scanning&#39;!<br>
zero<br>
        ^ (NumberFormatDescriptor newFrom: self) zero! !<br>
<br>
<br>
!FormatDescriptor methodsFor: &#39;printing&#39;!<br>
printOn: aStream<br>
        aStream nextPut: $%.<br>
        flush == #leftFlush ifTrue: [aStream nextPut: $-]! !<br>
<br>
!FormatDescriptor methodsFor: &#39;printing&#39;!<br>
printWidthOn: aStream<br>
        width ~= 0 ifTrue: [width printOn: aStream].<br>
        precision isNil ifFalse: [aStream nextPut: $.. precision printOn: aStream]! !<br>
<br>
&quot;-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- &quot;!<br>
<br>
FormatDescriptor class<br>
        instanceVariableNames: &#39;&#39;!<br>
<br>
!FormatDescriptor class methodsFor: &#39;class initialization&#39; stamp: &#39;mir 6/7/2000 00:21&#39;!<br>
initialize<br>
        &quot;FormatDescriptor initialize&quot;<br>
        Operators := Dictionary new.<br>
        Operators at: $p put: #PrintStringFormatDescriptor.<br>
        Operators at: $c put: #CharacterFormatDescriptor.<br>
        Operators at: $s put: #StringFormatDescriptor.<br>
        #($d $o $u $x $X)<br>
                do: [:operator | Operators at: operator put: #NumberFormatDescriptor].<br>
        #($e $E $f $g $G)<br>
                do: [:operator | Operators at: operator put: #FloatFormatDescriptor].<br>
<br>
        Flags := Dictionary new.<br>
        Flags at: $- put: #leftFlush.<br>
        Flags at: $+ put: #rightFlush.<br>
        Flags at: $  put: #space.<br>
        Flags at: $# put: #radix.<br>
        Flags at: $0 put: #zero.<br>
! !<br>
<br>
<br>
!FormatDescriptor class methodsFor: &#39;instance creation&#39;!<br>
new<br>
        ^ super new initialize! !<br>
<br>
!FormatDescriptor class methodsFor: &#39;instance creation&#39;!<br>
newFrom: desc<br>
        | myself |<br>
        myself := self new.<br>
        myself perform: desc flush.<br>
        myself width: desc width.<br>
        myself precision: desc precision.<br>
        ^ myself! !<br>
<br>
!FormatDescriptor class methodsFor: &#39;instance creation&#39;!<br>
scanFrom: stream<br>
        | desc |<br>
        desc := self new.<br>
        [Flags includesKey: stream peek]<br>
                whileTrue: [desc := desc perform: (Flags at: stream next)].<br>
        stream peek isDigit ifTrue: [desc width: (Integer readFrom: stream)].<br>
        stream peek == $. ifTrue: [stream next. desc precision: (Integer readFrom: stream)].<br>
        stream peek == $l ifTrue: [stream next].<br>
        desc := desc operator: stream next.<br>
        ^ desc! !<br>
<br>
FormatDescriptor subclass: #CharacterFormatDescriptor<br>
        instanceVariableNames: &#39;&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!CharacterFormatDescriptor methodsFor: &#39;rendering&#39;!<br>
applyOperator: object<br>
        ^ String with: object asCharacter! !<br>
<br>
<br>
!CharacterFormatDescriptor methodsFor: &#39;printing&#39;!<br>
printOn: aStream<br>
        super printOn: aStream.<br>
        self printWidthOn: aStream.<br>
        aStream nextPut: $c! !<br>
<br>
Object subclass: #FormatString<br>
        instanceVariableNames: &#39;format string composedString&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
!FormatString commentStamp: &#39;mir 6/7/2000 00:14&#39; prior: 0!<br>
Format description<br>
        syntax: %{flags}{width}{precision}{long}&lt;operator&gt;<br>
<br>
        flags<br>
                -               left flush<br>
                +               right flush<br>
                space   non-negative number are preceeded by a blank<br>
                #               display integer with a radix indicator (0=octal, 0x=hex, float have .)<br>
                0               0 is used as left padding character for numbers<br>
        width           minimum field width (rest is padded)<br>
        .precision      maximum field width or trailing digits<br>
        long            ignored<br>
        operator<br>
                c               display object as character<br>
                d               display as integer<br>
                e,E             float in scientific notation<br>
                f               display as float<br>
                g,G             display as f or e,E using least amount of space<br>
                o               display as octal value<br>
                s               display as string<br>
                u               display as unsigned<br>
                x,X             display as hex value<br>
        !<br>
<br>
<br>
!FormatString methodsFor: &#39;printf&#39;!<br>
&lt;&lt; object<br>
        &quot;Render object according to next format descriptor in format.<br>
        Append it to string&quot;<br>
        &quot;Format description<br>
        syntax: %{flags}{width}{precision}{long}&lt;operator&gt;<br>
<br>
        flags<br>
                -               left flush<br>
                +               right flush<br>
                space   non-negative number are preceeded by a blank<br>
                #               display integer with a radix indicator (0=octal, 0x=hex, float have .)<br>
                0               0 is used as left padding character for numbers<br>
        width           minimum field width (rest is padded)<br>
        .precision      maximum field width or trailing digits<br>
        long            ignored<br>
        operator<br>
                c               display object as character<br>
                d               display as integer<br>
                e,E             float in scientific notation<br>
                f               display as float<br>
                g,G             display as f or e,E using least amount of space<br>
                o               display as octal value<br>
                s               display as string<br>
                u               display as unsigned<br>
                x,X             display as hex value<br>
        &quot;<br>
<br>
        composedString nextPutAll: string next.<br>
        composedString nextPutAll: (format next render: object).<br>
        format atEnd<br>
                ifTrue:<br>
                        [format reset.<br>
                        composedString nextPutAll: string next.<br>
                        string reset].<br>
        ^composedString contents! !<br>
<br>
!FormatString methodsFor: &#39;printf&#39; stamp: &#39;hjo 9/17/2011 23:59&#39;!<br>
printf: arguments<br>
<br>
        &quot;inst var string holds all text contained in the formatstring. %f blabla %d&quot;<br>
        &quot;inst var format is a stream of FormatDescriptors&quot;<br>
<br>
        self reset.<br>
        arguments asArgumentArrayForFormatString do:<br>
                [:object |<br>
                &quot;put any text from the formatstring into composedstring&quot;<br>
                composedString nextPutAll: string next.<br>
                 &quot;get next FormatDescriptor from format and render object as specified&quot;<br>
                format atEnd ifFalse: [composedString nextPutAll: (format next render: object)]].<br>
        &quot;any remainder is string, if so append to composedString&quot;<br>
        string atEnd ifFalse: [composedString nextPutAll: string next].<br>
         ^self stringWithReset.! !<br>
<br>
!FormatString methodsFor: &#39;printf&#39;!<br>
string<br>
        ^composedString contents! !<br>
<br>
!FormatString methodsFor: &#39;printf&#39; stamp: &#39;hjo 9/17/2011 23:59&#39;!<br>
stringWithReset<br>
<br>
        | result |<br>
        result := self string.<br>
        self reset.<br>
        ^result! !<br>
<br>
<br>
!FormatString methodsFor: &#39;initialize-release&#39; stamp: &#39;hjo 9/18/2011 00:05&#39;!<br>
collectFormatDescriptorsAndStrings: formatStream<br>
<br>
        | done |<br>
        format := ReadWriteStream on: (Array new: 10).<br>
        string := ReadWriteStream on: (Array new: 10).<br>
        done := false.<br>
        [ done ]<br>
                whileFalse: [<br>
                        &quot;copy actual formatstrings to format&quot;<br>
                        string nextPut: (self scanStringFrom: formatStream).<br>
                        (done := formatStream atEnd)<br>
                                ifFalse: [<br>
                                        &quot;copy any nonformating text to string&quot;<br>
                                        format nextPut: (FormatDescriptor scanFrom: formatStream) ] ].<br>
        self reset! !<br>
<br>
!FormatString methodsFor: &#39;initialize-release&#39; stamp: &#39;hjo 9/18/2011 00:05&#39;!<br>
setFormat: aString<br>
        | formatStream |<br>
        &quot;copy actual formatstrings to format&quot;<br>
        &quot;copy any nonformating text to string&quot;<br>
        composedString := (String new: 20) writeStream.<br>
        formatStream := ((aString copyReplaceAll: &#39;\n&#39; with: (String with: Character cr))<br>
                copyReplaceAll: &#39;\t&#39;<br>
                with: (String with: Character tab)) readStream.<br>
        self collectFormatDescriptorsAndStrings: formatStream! !<br>
<br>
<br>
!FormatString methodsFor: &#39;private&#39;!<br>
reset<br>
        format reset.<br>
        string reset.<br>
        composedString reset! !<br>
<br>
!FormatString methodsFor: &#39;private&#39; stamp: &#39;hjo 9/18/2011 00:00&#39;!<br>
scanStringFrom: aStream<br>
        | newString |<br>
        newString := (String new: 40) writeStream.<br>
        [aStream atEnd]<br>
                whileFalse:<br>
                        [| next |<br>
                        next := aStream next.<br>
                        next == $% ifTrue: [^newString contents].<br>
                        next == $\<br>
                                ifTrue:<br>
                                        [next := aStream next.<br>
                                        next == $n ifTrue: [next := Character cr].<br>
                                        next == $t ifTrue: [next := Character tab]].<br>
                        newString nextPut: next].<br>
        ^newString contents! !<br>
<br>
&quot;-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- &quot;!<br>
<br>
FormatString class<br>
        instanceVariableNames: &#39;&#39;!<br>
<br>
!FormatString class methodsFor: &#39;examples&#39; stamp: &#39;mir 6/7/2000 00:12&#39;!<br>
examples<br>
        self inform: (&#39;Here is a string &quot;%s&quot;.&#39; printf: &#39;hello world&#39;).<br>
        self inform: (&#39;Here is a string &quot;%s&quot; and another shortened &quot;%-14.7s&quot;.&#39;<br>
                printf: #(&#39;hello world&#39; &#39;hello world&#39;)).<br>
<br>
        self inform: (&#39;Here is a number &quot;%d&quot;.&#39; printf: 42).<br>
        self inform: (&#39;Here is a string &quot;%07.7d&quot;.&#39; printf: 42).<br>
<br>
        self inform: (&#39;Here is a number &quot;%e&quot;.&#39; printf: 42.0).<br>
        self inform: (&#39;Here is a float &quot;%e&quot; and an integer &quot;%d&quot;.&#39; printf: #(42.0 42)).<br>
        self inform: (&#39;Here is a string &quot;%013.5e&quot;.&#39; printf: 42.1234567).<br>
<br>
        self inform: (&#39;Here is a %s string &quot;%s&quot; and the same shortened &quot;%-14.7s&quot; with left flush.\nThe new line has a number &quot;%e&quot; and a 0-padded limited precision one &quot;%013.5e&quot;.&#39;<br>


                printf: ((Array with: &#39;long&#39; with: &#39;hello world&#39; with: &#39;hello world&#39; with: 42.0) copyWith: 42.1234567)).! !<br>
<br>
TestCase subclass: #FormatStringTest<br>
        instanceVariableNames: &#39;&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:41&#39;!<br>
testManyArguments<br>
<br>
        self assert: &#39;Here is a long string &quot;hello world&quot; and the same shortened &quot;hello w       &quot; with left flush.<br>
The new line has a number &quot;42.0&quot; and a 0-padded limited precision one &quot;0000042.12345&quot;.&#39; equals: (&#39;Here is a %s string &quot;%s&quot; and the same shortened &quot;%-14.7s&quot; with left flush.\nThe new line has a number &quot;%e&quot; and a 0-padded limited precision one &quot;%013.5e&quot;.&#39;<br>


                printf: ((Array with: &#39;long&#39; with: &#39;hello world&#39; with: &#39;hello world&#39; with: 42.0) copyWith: 42.1234567)).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:41&#39;!<br>
testOneExponent<br>
<br>
        self assert: &#39;Here is a number &quot;42.0&quot;.&#39; equals: (&#39;Here is a number &quot;%e&quot;.&#39; printf: 42.0).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:41&#39;!<br>
testOneExponentAndOneInteger<br>
<br>
        self assert: &#39;Here is a float &quot;42.0&quot; and an integer &quot;42&quot;.&#39; equals: (&#39;Here is a float &quot;%e&quot; and an integer &quot;%d&quot;.&#39; printf: #(42.0 42)).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:41&#39;!<br>
testOneExponentWithLength<br>
<br>
        self assert: &#39;Here is a string &quot;0000042.12345&quot;.&#39; equals: (&#39;Here is a string &quot;%013.5e&quot;.&#39; printf: 42.1234567).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:40&#39;!<br>
testOneInteger<br>
<br>
        self assert: &#39;Here is a number &quot;42&quot;.&#39; equals: (&#39;Here is a number &quot;%d&quot;.&#39; printf: 42).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:40&#39;!<br>
testOneIntegerWithLength<br>
<br>
        self assert: &#39;Here is a string &quot;0000042&quot;.&#39; equals: (&#39;Here is a string &quot;%07.7d&quot;.&#39; printf: 42).! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:40&#39;!<br>
testOneString<br>
<br>
        self assert: &#39;Here is a string &quot;hello world&quot;.&#39; equals: (&#39;Here is a string &quot;%s&quot;.&#39; printf: &#39;hello world&#39;)! !<br>
<br>
!FormatStringTest methodsFor: &#39;as yet unclassified&#39; stamp: &#39;hjo 9/17/2011 23:40&#39;!<br>
testOneStringWithLength<br>
<br>
        self assert:  &#39;Here is a string &quot;hello world&quot; and another shortened &quot;hello w       &quot;.&#39; equals: (&#39;Here is a string &quot;%s&quot; and another shortened &quot;%-14.7s&quot;.&#39; printf: #(&#39;hello world&#39; &#39;hello world&#39;))! !<br>


<br>
FormatDescriptor subclass: #NumberFormatDescriptor<br>
        instanceVariableNames: &#39;operator padding radix space&#39;<br>
        classVariableNames: &#39;Base Radix&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;mir 6/6/2000 23:56&#39;!<br>
applyOperator: object<br>
        &quot;Character and Number are the only valid classes&quot;<br>
<br>
        | number string |<br>
        object isNil ifTrue: [^&#39;-&#39;].<br>
&quot;object isInteger ifFalse: [self halt].<br>
&quot;       number := object asInteger.<br>
        string := number printStringBase: self base.<br>
        radix ifTrue: [string := self radixString , string].<br>
        (space and: [operator == $d and: [number &lt; 0]])<br>
                ifTrue: [string := &#39; &#39; , string].<br>
        ^ (width ~= 0 and: [string size &gt; self stringLength])<br>
                ifTrue: [String new: width withAll: $*]<br>
                ifFalse: [string]! !<br>
<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
base<br>
        ^ Base at: operator! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
padding<br>
        ^ padding! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
radixString<br>
        ^ Radix at: operator! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
setOperator: char<br>
        operator := char! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
setPadding: paddingChar<br>
        padding := paddingChar! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;private&#39;!<br>
stringLength<br>
        ^precision isNil<br>
                ifTrue: [SmallInteger maxVal]<br>
                ifFalse: [precision]! !<br>
<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;initialize-release&#39;!<br>
initialize<br>
        super initialize.<br>
        padding := $ .<br>
        radix := false.<br>
        space := false! !<br>
<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;printing&#39;!<br>
printOn: aStream<br>
        super printOn: aStream.<br>
        padding == $0 ifTrue: [aStream nextPut: $0].<br>
        radix ifTrue: [aStream nextPut: $#].<br>
        space ifTrue: [aStream nextPut: $ ].<br>
        self printWidthOn: aStream.<br>
        aStream nextPut: operator! !<br>
<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;scanning&#39;!<br>
radix<br>
        radix := true! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;scanning&#39;!<br>
space<br>
        space := true! !<br>
<br>
!NumberFormatDescriptor methodsFor: &#39;scanning&#39;!<br>
zero<br>
        padding := $0! !<br>
<br>
&quot;-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- &quot;!<br>
<br>
NumberFormatDescriptor class<br>
        instanceVariableNames: &#39;&#39;!<br>
<br>
!NumberFormatDescriptor class methodsFor: &#39;class initialization&#39;!<br>
initialize<br>
        &quot;NumberFormatDescriptor initialize&quot;<br>
        Base := Dictionary new.<br>
        Base at: $d put: 10.<br>
        Base at: $o put: 8.<br>
        Base at: $u put: 10.<br>
        Base at: $x put: 16.<br>
        Base at: $X put: 16.<br>
<br>
        Radix := Dictionary new.<br>
        Radix at: $d put: &#39;&#39;.<br>
        Radix at: $o put: &#39;0&#39;.<br>
        Radix at: $u put: &#39;&#39;.<br>
        Radix at: $x put: &#39;0x&#39;.<br>
        Radix at: $X put: &#39;0X&#39;.! !<br>
<br>
<br>
!NumberFormatDescriptor class methodsFor: &#39;instance creation&#39;!<br>
newFrom: desc<br>
        desc class == self ifTrue: [^ desc].<br>
        ^ (super newFrom: desc) setPadding: desc padding! !<br>
<br>
NumberFormatDescriptor subclass: #FloatFormatDescriptor<br>
        instanceVariableNames: &#39;&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!FloatFormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;hjo 9/18/2011 00:47&#39;!<br>
applyOperator: object<br>
        &quot;Number is the only valid class&quot;<br>
<br>
        | string |<br>
        string := self zeroPaddedStringOfBase10ForFloat: object asFloat.<br>
        string := string copyFrom: 1 to: ((string indexOf: $.) + (precision == 0<br>
                                                ifTrue: [-1]<br>
                                                ifFalse: [self precision]) min: string size).<br>
        (space and: [object asFloat &gt;= 0])<br>
                ifTrue: [string := &#39; &#39; , string].<br>
        ^(width ~= 0 and: [string size &gt; width])<br>
                ifTrue: [String new: width withAll: $*]<br>
                ifFalse: [string]! !<br>
<br>
!FloatFormatDescriptor methodsFor: &#39;rendering&#39; stamp: &#39;hjo 9/18/2011 00:45&#39;!<br>
zeroPaddedStringOfBase10ForFloat: aFloat<br>
<br>
        | stream |<br>
        stream := String new writeStream.<br>
        aFloat printOn: stream base: 10.<br>
        stream next: self precision-1 put: $0.<br>
        ^stream contents.<br>
! !<br>
<br>
<br>
!FloatFormatDescriptor methodsFor: &#39;private&#39; stamp: &#39;mir 6/7/2000 00:01&#39;!<br>
digits<br>
        ^ width == 0 ifTrue: [7] ifFalse: [width]! !<br>
<br>
!FloatFormatDescriptor methodsFor: &#39;private&#39;!<br>
precision<br>
        ^ precision isNil ifTrue: [1] ifFalse: [precision]! !<br>
<br>
!FloatFormatDescriptor methodsFor: &#39;private&#39;!<br>
stringLength<br>
        ^ width! !<br>
<br>
FormatDescriptor subclass: #StringFormatDescriptor<br>
        instanceVariableNames: &#39;&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!StringFormatDescriptor methodsFor: &#39;rendering&#39;!<br>
applyOperator: object<br>
        ^ object! !<br>
<br>
<br>
!StringFormatDescriptor methodsFor: &#39;printing&#39;!<br>
printOn: aStream<br>
        super printOn: aStream.<br>
        self printWidthOn: aStream.<br>
        aStream nextPut: $s! !<br>
<br>
StringFormatDescriptor subclass: #PrintStringFormatDescriptor<br>
        instanceVariableNames: &#39;&#39;<br>
        classVariableNames: &#39;&#39;<br>
        poolDictionaries: &#39;&#39;<br>
        category: &#39;Printf&#39;!<br>
<br>
!PrintStringFormatDescriptor methodsFor: &#39;rendering&#39;!<br>
applyOperator: object<br>
        ^ object printLeanString! !<br>
<br>
<br>
!PrintStringFormatDescriptor methodsFor: &#39;printing&#39;!<br>
printOn: aStream<br>
        aStream nextPut: $%.<br>
        flush == #leftFlush ifTrue: [aStream nextPut: $-].<br>
        self printWidthOn: aStream.<br>
        aStream nextPut: $p! !<br>
<br>
FormatDescriptor initialize!<br>
NumberFormatDescriptor initialize!<br>
</blockquote></div><br></div>