extensions.st
changeset 2241 81f10d4ad4bf
parent 2239 342ce4db5707
child 2256 10583ebc7f64
--- a/extensions.st	Mon Sep 14 19:49:05 2009 +0200
+++ b/extensions.st	Mon Sep 14 23:59:34 2009 +0200
@@ -92,6 +92,436 @@
     "
 ! !
 
+!CharacterArray methodsFor:'printing & storing'!
+
+printf:args 
+    "Format and print the receiver with <args> formatted in C style, as 
+     specified in the Unix C-language manual page for printf(3).
+
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |aStream|
+
+    aStream := WriteStream on:String new.
+    self printf_printOn:aStream withData:args.
+    ^ aStream contents
+
+    "
+     Transcript showCR: 'Some examples:'!!
+
+     Transcript show:'''%#x %#X %03o%*.*s'' printf: #(16rABCD 16rEF 5 9 5 ''ghijklmn'') = .'.
+     Transcript show: ('%#x %#X %03o%*.*s' printf: #(16rABCD 16rEF 5 9 5 'ghijklmn')).  
+     Transcript showCR: '.'
+
+     Transcript show: '''%- 10.4s%.2e'' printf: (Array with: ''abcdefghijkl'' with: Float pi) = .'.
+     Transcript show: ('%- 10.4s%.2e' printf: (Array with: 'abcdefghijkl' with: Float pi)).  
+     Transcript showCR: '.'
+
+     Transcript show: '''%8.3f'' printf: (Array with: 200 sqrt negated) = .'.
+     Transcript show: ('%8.3f' printf: (Array with: 200 sqrt negated)).
+     Transcript showCR: '.'
+
+     Transcript show: '''%c'' printf: #(16r41) = .'.
+     Transcript show: ('%c' printf: #(16r41)).
+     Transcript showCR: '.'
+
+     Transcript show: '''%f%2s%s%s%s'' sscanf: ''237.0 this is a test'' = '.
+     Transcript showCR: ('%f%2s%s%s%s'  sscanf: '237.0 this is a test') printString.
+
+     Transcript show: '''%d%f%s'' sscanf: ''25 54.32e-01 monday'' = '.
+     Transcript showCR: ('%d%f%s' sscanf: '25 54.32e-01 monday') printString.
+
+     Transcript show: '''%f%*f %8[A-F0-9]%c%d 0x%x%f'' sscanf: ''12.45 1048.73 AE40Z527 0x75BCD15 34'' = '.
+     Transcript showCR: ('%f%*f %8[A-F0-9]%c%d 0x%x%f' sscanf: '12.45 1048.73 AE40Z527 0x75BCD15 34') printString.
+    "
+! !
+
+!CharacterArray methodsFor:'printing & storing'!
+
+printf_formatArgCount
+    "Return the number of arguments required/produced if the receiver is interpreted
+     as a printf/scanf format control string.
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |nonConsecutive count|
+
+    nonConsecutive := true.
+    count := 0.
+    self do:[:c | 
+        c == $% ifTrue:[
+            nonConsecutive ifTrue:[
+                count := count + 1.
+                nonConsecutive := false
+            ] ifFalse:[
+                count := count - 1.
+                nonConsecutive := true
+            ]
+        ] ifFalse:[
+            nonConsecutive := true
+        ]
+    ].
+    ^ count
+! !
+
+!CharacterArray methodsFor:'private'!
+
+printf_printArgFrom:inStream to:outStream withData:argStream 
+    "Interpret the required number of arguments from <argStream>
+     according to the formatting information in <inStream>.  
+     Place the interpretation on <outStream>.  
+     The interpretation is C printf(3) style, as
+     specified in the Unix C-language manual page for printf(3).
+     <inStream> is assumed to be positioned just past
+     $%, and a complete control string is assumed available.
+
+     Return when the conversion control string is consumed.  
+     Leave <inStream> pointing past the last character in the conversion control string.
+
+     This code assumes that <inStream> is formatted according to
+     specification, and error checking is minimal.  Unexpected
+     results will be obtained by illegal control strings, or when
+     argument types do not match conversion codes, but it probably
+     won't dump core, like C does in such cases!!
+
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |ljust plus pound width precision pad char arg argString|
+
+    ljust := plus := pound := false.
+    width := 0.
+    precision := SmallInteger maxVal.
+    pad := $ .
+    char := inStream peek.
+    char == $% ifTrue:[
+        ^ outStream nextPut:inStream next
+    ].
+    char == $- ifTrue:[
+        ljust := true.
+        inStream next.
+        char := inStream peek
+    ].
+    char == $  ifTrue:[
+        outStream space.
+        inStream next.
+        char := inStream peek
+    ].
+    char == $+ ifTrue:[
+        plus := true.
+        inStream next.
+        char := inStream peek
+    ].
+    char == $# ifTrue:[
+        pound := true.
+        inStream next.
+        char := inStream peek
+    ].
+    char == $* ifTrue:[
+        width := argStream next.
+        inStream next.
+        char := inStream peek
+    ].
+    char isDigit ifTrue:[
+        char == $0 ifTrue:[
+            pad := $0
+        ].
+        width := Integer readFrom:inStream.
+        char := inStream peek
+    ].
+    char == $. ifTrue:[
+        inStream next.
+        char := inStream peek.
+        char == $* ifTrue:[
+            precision := argStream next.
+            inStream next.
+            char := inStream peek
+        ] ifFalse:[
+            precision := Integer readFrom:inStream.
+            char := inStream peek
+        ]
+    ].
+    char == $l "Ignore long specifier." ifTrue:[
+        inStream next.
+        char := inStream peek
+    ].
+    ('feg' includes:char) ifTrue:[
+        arg := argStream next asFloat.
+        precision := precision min:6.
+        argString := WriteStream on:VariableString "String" new.
+        char == $g ifTrue:[
+            arg absPrintOn:argString digits:precision + 1
+        ].
+        char == $f ifTrue:[
+            arg absDecimalPrintOn:argString digits:precision + arg abs log + 1
+        ].
+        char == $e ifTrue:[
+            arg absScientificPrintOn:argString digits:precision + 1
+        ].
+        argString := argString contents.
+        arg < 0 ifTrue:[
+            argString := '-' , argString
+        ] ifFalse:[
+            plus ifTrue:[
+                argString := '+' , argString
+            ]
+        ].
+        (precision = 0 and:[ pound not ]) ifTrue:[
+            (argString includes:$e) ifTrue:[
+                "self halt"
+            ] ifFalse:[
+                argString := arg truncated printString
+            ]
+        ].
+        pound ifTrue:[
+            (argString includes:$e) ifTrue:[
+                "self halt"
+            ] ifFalse:[
+                precision - (argString size - (argString indexOf:$.)) timesRepeat:[
+                    argString := argString , '0'
+                ]
+            ]
+        ].
+        ljust ifTrue:[
+            outStream nextPutAll:argString
+        ].
+        width - argString size timesRepeat:[
+            outStream space
+        ].
+        ljust ifFalse:[
+            outStream nextPutAll:argString
+        ].
+        ^ inStream next
+    ].
+    char == $c ifTrue:[
+        arg := String with:argStream next asCharacter
+    ].
+    char == $s "Assume the arg is a String or Symbol." ifTrue:[
+        arg := argStream next asString
+    ].
+    char == $d ifTrue:[
+        arg := argStream next asInteger printString.
+        plus ifTrue:[
+            arg := '+' , arg
+        ]
+    ].
+    char == $u ifTrue:[
+        arg := argStream next asInteger abs printString
+    ].
+    char == $o ifTrue:[
+        arg := argStream next asInteger abs printStringRadix:8.
+        pound ifTrue:[
+            arg := '0' , arg
+        ]
+    ].
+    ('xX' includes:char) ifTrue:[
+        arg := argStream next asInteger abs printStringRadix:16.
+        pound ifTrue:[
+            arg := '0x' , arg
+        ]
+    ].
+    char == $x ifTrue:[
+        1 to:arg size do:[:i | 
+            ('ABCDEF' includes:(arg at:i)) ifTrue:[
+                arg at:i put:((arg at:i) asciiValue + 16r20) asCharacter
+            ]
+        ]
+    ].
+    precision := precision min:arg size.
+    ljust ifTrue:[
+        outStream nextPutAll:(arg copyFrom:1 to:precision)
+    ].
+    width - precision timesRepeat:[
+        outStream nextPut:pad
+    ].
+    ljust ifFalse:[
+        outStream nextPutAll:(arg copyFrom:1 to:precision)
+    ].
+    ^ inStream next
+! !
+
+!CharacterArray methodsFor:'printing & storing'!
+
+printf_printOn:outStream withData:args 
+    "Format and print the receiver on <outStream> with <args>
+     formatted in C style, as specified in the Unix C-language manual page for printf(3).
+
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |argStream inStream char|
+
+    argStream := ReadStream on:args.
+    inStream := ReadStream on:self.
+    [ inStream atEnd ] whileFalse:[
+        (char := inStream next) == $% ifFalse:[
+            outStream nextPut:char
+        ] ifTrue:[
+            self 
+                printf_printArgFrom:inStream
+                to:outStream
+                withData:argStream
+        ]
+    ]
+! !
+
+!CharacterArray methodsFor:'converting'!
+
+scanf:dataStream 
+    "Return a Collection of objects found in the Character Stream
+     <dataStream> as interpreted according to the receiver.  
+     The receiver is assumed to be a conversion control string as
+     specified in the Unix C-language manual page for scanf(3).
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |results format char|
+
+    results := OrderedCollection new.
+    format := ReadStream on:self.
+    [ format atEnd ] whileFalse:[
+        char := format next.
+        (char == Character space or:[ char == Character tab ]) ifTrue:[
+            dataStream skipSeparators.
+            format skipSeparators
+        ].
+        char == $% ifTrue:[
+            self 
+                scanf_scanArgFrom:dataStream
+                to:results
+                format:format
+        ] ifFalse:[
+            dataStream peekFor:char
+        ]
+    ].
+    ^ results
+
+    "
+     '%d %x' scanf:(ReadStream on:'1234 ff00')    
+    "
+! !
+
+!CharacterArray methodsFor:'private'!
+
+scanf_scanArgFrom:dataStream to:collection format:format 
+    "Add to <collection> an object who's representation is found
+     in <dataStream> interpreted according to the conversion
+     control string in the Stream <format>.  
+     <format> is assumed to be positioned just past a $%, and a complete control 
+     string is assumed available.
+
+     Return when the conversion control string is consumed.  Leave
+     <format> pointing past the last character in the conversion
+     control string, leave <dataStream> pointing past any width
+     specified in <format>, or at the first character that doesn't
+     make sense for the <format>.
+
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    |final width char pos data scanset exclusive return last|
+
+    final := [:retval | 
+            collection add:retval.
+            data == dataStream ifFalse:[
+                dataStream position:dataStream position + data position
+            ].
+            ^ self
+        ].
+    width := 0.
+    char := format peek.
+    char == $% ifTrue:[
+        ^ dataStream peekFor:char
+    ].
+    char == $* ifTrue:[
+        format next.
+        char := format peek.
+        final := [:retval | 
+                data == dataStream ifFalse:[
+                    dataStream position:dataStream position + data position
+                ].
+                ^ self
+            ]
+    ].
+    char isDigit ifTrue:[
+        width := Integer readFrom:format.
+        char := format peek
+    ].
+    ('slhduoxfeg' includes:char) ifTrue:[
+        dataStream skipSeparators
+    ].
+    width = 0 ifTrue:[
+        data := dataStream
+    ] ifFalse:[
+        pos := dataStream position.
+        data := ReadStream on:(dataStream next:width).
+        dataStream position:pos
+    ].
+    char == $s ifTrue:[
+        final value:(data upToSeparator)
+    ].
+    char == $c ifTrue:[
+        width = 0 ifTrue:[
+            final value:(String with:data next)
+        ] ifFalse:[
+            final value:data contents
+        ]
+    ].
+    char == $[ "What a mess!!" ifTrue:[
+        return := WriteStream on:(VariableString "String" new:8).
+        scanset := IdentitySet new.
+        format next.
+        width = 0 ifTrue:[
+            width := SmallInteger maxVal
+        ].
+        exclusive := format peekFor:$^.
+        [
+            last := char.
+            char := format next.
+            char == $]
+        ] whileFalse:[
+            char == $- ifFalse:[
+                scanset add:char
+            ] ifTrue:[
+                (last to:format next) do:[:c | 
+                    scanset add:c
+                ]
+            ]
+        ].
+        [
+            data atEnd not and:[ (scanset includes:data peek) xor:exclusive ]
+        ] whileTrue:[ return nextPut:data next ].
+        final value:return contents
+    ].
+    ('lh' includes:char) ifTrue:[
+        format next.
+        char := format peek
+    ].
+    ('DUdu' includes:char) ifTrue:[
+        final value:(Integer readFrom:data)
+    ].
+    ('FEGfeg' includes:char) ifTrue:[
+        final value:(Float readFrom:data)
+    ].
+    ('Oo' includes:char) ifTrue:[
+        final value:(Integer readFrom:data radix:8)
+    ].
+    ('Xx' includes:char) ifTrue:[
+        final value:(Integer readFrom:data radix:16)
+    ]
+! !
+
+!CharacterArray methodsFor:'converting'!
+
+sscanf:string 
+    "Return a Collection of objects found in <string> as
+     interpreted according to the receiver. 
+     The receiver is assumed to be a conversion control string as
+     specified in the Unix C-language manual page for scanf(3).
+     For copyright information, see goodies/String-printf_scanf.chg"
+    
+    ^ self scanf:(ReadStream on:string)
+
+    "
+     '%d %x' sscanf:'1234 ff00'    
+    "
+! !
+
 !Float methodsFor:'private'!
 
 absDecimalPrintOn:aStream digits:digits 
@@ -609,433 +1039,3 @@
     "
 ! !
 
-!String methodsFor:'printing'!
-
-printf:args 
-    "Format and print the receiver with <args> formatted in C style, as 
-     specified in the Unix C-language manual page for printf(3).
-
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |aStream|
-
-    aStream := WriteStream on:String new.
-    self printf_printOn:aStream withData:args.
-    ^ aStream contents
-
-    "
-     Transcript showCR: 'Some examples:'!!
-
-     Transcript show:'''%#x %#X %03o%*.*s'' printf: #(16rABCD 16rEF 5 9 5 ''ghijklmn'') = .'.
-     Transcript show: ('%#x %#X %03o%*.*s' printf: #(16rABCD 16rEF 5 9 5 'ghijklmn')).  
-     Transcript showCR: '.'
-
-     Transcript show: '''%- 10.4s%.2e'' printf: (Array with: ''abcdefghijkl'' with: Float pi) = .'.
-     Transcript show: ('%- 10.4s%.2e' printf: (Array with: 'abcdefghijkl' with: Float pi)).  
-     Transcript showCR: '.'
-
-     Transcript show: '''%8.3f'' printf: (Array with: 200 sqrt negated) = .'.
-     Transcript show: ('%8.3f' printf: (Array with: 200 sqrt negated)).
-     Transcript showCR: '.'
-
-     Transcript show: '''%c'' printf: #(16r41) = .'.
-     Transcript show: ('%c' printf: #(16r41)).
-     Transcript showCR: '.'
-
-     Transcript show: '''%f%2s%s%s%s'' sscanf: ''237.0 this is a test'' = '.
-     Transcript showCR: ('%f%2s%s%s%s'  sscanf: '237.0 this is a test') printString.
-
-     Transcript show: '''%d%f%s'' sscanf: ''25 54.32e-01 monday'' = '.
-     Transcript showCR: ('%d%f%s' sscanf: '25 54.32e-01 monday') printString.
-
-     Transcript show: '''%f%*f %8[A-F0-9]%c%d 0x%x%f'' sscanf: ''12.45 1048.73 AE40Z527 0x75BCD15 34'' = '.
-     Transcript showCR: ('%f%*f %8[A-F0-9]%c%d 0x%x%f' sscanf: '12.45 1048.73 AE40Z527 0x75BCD15 34') printString.
-    "
-! !
-
-!String methodsFor:'printing'!
-
-printf_formatArgCount
-    "Return the number of arguments required/produced if the receiver is interpreted
-     as a printf/scanf format control string.
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |nonConsecutive count|
-
-    nonConsecutive := true.
-    count := 0.
-    self do:[:c | 
-        c == $% ifTrue:[
-            nonConsecutive ifTrue:[
-                count := count + 1.
-                nonConsecutive := false
-            ] ifFalse:[
-                count := count - 1.
-                nonConsecutive := true
-            ]
-        ] ifFalse:[
-            nonConsecutive := true
-        ]
-    ].
-    ^ count
-! !
-
-!String methodsFor:'private'!
-
-printf_printArgFrom:inStream to:outStream withData:argStream 
-    "Interpret the required number of arguments from <argStream>
-     according to the formatting information in <inStream>.  
-     Place the interpretation on <outStream>.  
-     The interpretation is C printf(3) style, as
-     specified in the Unix C-language manual page for printf(3).
-     <inStream> is assumed to be positioned just past
-     $%, and a complete control string is assumed available.
-
-     Return when the conversion control string is consumed.  
-     Leave <inStream> pointing past the last character in the conversion control string.
-
-     This code assumes that <inStream> is formatted according to
-     specification, and error checking is minimal.  Unexpected
-     results will be obtained by illegal control strings, or when
-     argument types do not match conversion codes, but it probably
-     won't dump core, like C does in such cases!!
-
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |ljust plus pound width precision pad char arg argString|
-
-    ljust := plus := pound := false.
-    width := 0.
-    precision := SmallInteger maxVal.
-    pad := $ .
-    char := inStream peek.
-    char == $% ifTrue:[
-        ^ outStream nextPut:inStream next
-    ].
-    char == $- ifTrue:[
-        ljust := true.
-        inStream next.
-        char := inStream peek
-    ].
-    char == $  ifTrue:[
-        outStream space.
-        inStream next.
-        char := inStream peek
-    ].
-    char == $+ ifTrue:[
-        plus := true.
-        inStream next.
-        char := inStream peek
-    ].
-    char == $# ifTrue:[
-        pound := true.
-        inStream next.
-        char := inStream peek
-    ].
-    char == $* ifTrue:[
-        width := argStream next.
-        inStream next.
-        char := inStream peek
-    ].
-    char isDigit ifTrue:[
-        char == $0 ifTrue:[
-            pad := $0
-        ].
-        width := Integer readFrom:inStream.
-        char := inStream peek
-    ].
-    char == $. ifTrue:[
-        inStream next.
-        char := inStream peek.
-        char == $* ifTrue:[
-            precision := argStream next.
-            inStream next.
-            char := inStream peek
-        ] ifFalse:[
-            precision := Integer readFrom:inStream.
-            char := inStream peek
-        ]
-    ].
-    char == $l "Ignore long specifier." ifTrue:[
-        inStream next.
-        char := inStream peek
-    ].
-    ('feg' includes:char) ifTrue:[
-        arg := argStream next asFloat.
-        precision := precision min:6.
-        argString := WriteStream on:VariableString "String" new.
-        char == $g ifTrue:[
-            arg absPrintOn:argString digits:precision + 1
-        ].
-        char == $f ifTrue:[
-            arg absDecimalPrintOn:argString digits:precision + arg abs log + 1
-        ].
-        char == $e ifTrue:[
-            arg absScientificPrintOn:argString digits:precision + 1
-        ].
-        argString := argString contents.
-        arg < 0 ifTrue:[
-            argString := '-' , argString
-        ] ifFalse:[
-            plus ifTrue:[
-                argString := '+' , argString
-            ]
-        ].
-        (precision = 0 and:[ pound not ]) ifTrue:[
-            (argString includes:$e) ifTrue:[
-                "self halt"
-            ] ifFalse:[
-                argString := arg truncated printString
-            ]
-        ].
-        pound ifTrue:[
-            (argString includes:$e) ifTrue:[
-                "self halt"
-            ] ifFalse:[
-                precision - (argString size - (argString indexOf:$.)) timesRepeat:[
-                    argString := argString , '0'
-                ]
-            ]
-        ].
-        ljust ifTrue:[
-            outStream nextPutAll:argString
-        ].
-        width - argString size timesRepeat:[
-            outStream space
-        ].
-        ljust ifFalse:[
-            outStream nextPutAll:argString
-        ].
-        ^ inStream next
-    ].
-    char == $c ifTrue:[
-        arg := String with:argStream next asCharacter
-    ].
-    char == $s "Assume the arg is a String or Symbol." ifTrue:[
-        arg := argStream next asString
-    ].
-    char == $d ifTrue:[
-        arg := argStream next asInteger printString.
-        plus ifTrue:[
-            arg := '+' , arg
-        ]
-    ].
-    char == $u ifTrue:[
-        arg := argStream next asInteger abs printString
-    ].
-    char == $o ifTrue:[
-        arg := argStream next asInteger abs printStringRadix:8.
-        pound ifTrue:[
-            arg := '0' , arg
-        ]
-    ].
-    ('xX' includes:char) ifTrue:[
-        arg := argStream next asInteger abs printStringRadix:16.
-        pound ifTrue:[
-            arg := '0x' , arg
-        ]
-    ].
-    char == $x ifTrue:[
-        1 to:arg size do:[:i | 
-            ('ABCDEF' includes:(arg at:i)) ifTrue:[
-                arg at:i put:((arg at:i) asciiValue + 16r20) asCharacter
-            ]
-        ]
-    ].
-    precision := precision min:arg size.
-    ljust ifTrue:[
-        outStream nextPutAll:(arg copyFrom:1 to:precision)
-    ].
-    width - precision timesRepeat:[
-        outStream nextPut:pad
-    ].
-    ljust ifFalse:[
-        outStream nextPutAll:(arg copyFrom:1 to:precision)
-    ].
-    ^ inStream next
-! !
-
-!String methodsFor:'printing'!
-
-printf_printOn:outStream withData:args 
-    "Format and print the receiver on <outStream> with <args>
-     formatted in C style, as specified in the Unix C-language manual page for printf(3).
-
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |argStream inStream char|
-
-    argStream := ReadStream on:args.
-    inStream := ReadStream on:self.
-    [ inStream atEnd ] whileFalse:[
-        (char := inStream next) == $% ifFalse:[
-            outStream nextPut:char
-        ] ifTrue:[
-            self 
-                printf_printArgFrom:inStream
-                to:outStream
-                withData:argStream
-        ]
-    ]
-! !
-
-!String methodsFor:'converting'!
-
-scanf:dataStream 
-    "Return a Collection of objects found in the Character Stream
-     <dataStream> as interpreted according to the receiver.  
-     The receiver is assumed to be a conversion control string as
-     specified in the Unix C-language manual page for scanf(3).
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |results format char|
-
-    results := OrderedCollection new.
-    format := ReadStream on:self.
-    [ format atEnd ] whileFalse:[
-        char := format next.
-        (char == Character space or:[ char == Character tab ]) ifTrue:[
-            dataStream skipSeparators.
-            format skipSeparators
-        ].
-        char == $% ifTrue:[
-            self 
-                scanf_scanArgFrom:dataStream
-                to:results
-                format:format
-        ] ifFalse:[
-            dataStream peekFor:char
-        ]
-    ].
-    ^ results
-
-    "
-     '%d %x' scanf:(ReadStream on:'1234 ff00')    
-    "
-! !
-
-!String methodsFor:'private'!
-
-scanf_scanArgFrom:dataStream to:collection format:format 
-    "Add to <collection> an object who's representation is found
-     in <dataStream> interpreted according to the conversion
-     control string in the Stream <format>.  
-     <format> is assumed to be positioned just past a $%, and a complete control 
-     string is assumed available.
-
-     Return when the conversion control string is consumed.  Leave
-     <format> pointing past the last character in the conversion
-     control string, leave <dataStream> pointing past any width
-     specified in <format>, or at the first character that doesn't
-     make sense for the <format>.
-
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    |final width char pos data scanset exclusive return last|
-
-    final := [:retval | 
-            collection add:retval.
-            data == dataStream ifFalse:[
-                dataStream position:dataStream position + data position
-            ].
-            ^ self
-        ].
-    width := 0.
-    char := format peek.
-    char == $% ifTrue:[
-        ^ dataStream peekFor:char
-    ].
-    char == $* ifTrue:[
-        format next.
-        char := format peek.
-        final := [:retval | 
-                data == dataStream ifFalse:[
-                    dataStream position:dataStream position + data position
-                ].
-                ^ self
-            ]
-    ].
-    char isDigit ifTrue:[
-        width := Integer readFrom:format.
-        char := format peek
-    ].
-    ('slhduoxfeg' includes:char) ifTrue:[
-        dataStream skipSeparators
-    ].
-    width = 0 ifTrue:[
-        data := dataStream
-    ] ifFalse:[
-        pos := dataStream position.
-        data := ReadStream on:(dataStream next:width).
-        dataStream position:pos
-    ].
-    char == $s ifTrue:[
-        final value:(data upToSeparator)
-    ].
-    char == $c ifTrue:[
-        width = 0 ifTrue:[
-            final value:(String with:data next)
-        ] ifFalse:[
-            final value:data contents
-        ]
-    ].
-    char == $[ "What a mess!!" ifTrue:[
-        return := WriteStream on:(VariableString "String" new:8).
-        scanset := IdentitySet new.
-        format next.
-        width = 0 ifTrue:[
-            width := SmallInteger maxVal
-        ].
-        exclusive := format peekFor:$^.
-        [
-            last := char.
-            char := format next.
-            char == $]
-        ] whileFalse:[
-            char == $- ifFalse:[
-                scanset add:char
-            ] ifTrue:[
-                (last to:format next) do:[:c | 
-                    scanset add:c
-                ]
-            ]
-        ].
-        [
-            data atEnd not and:[ (scanset includes:data peek) xor:exclusive ]
-        ] whileTrue:[ return nextPut:data next ].
-        final value:return contents
-    ].
-    ('lh' includes:char) ifTrue:[
-        format next.
-        char := format peek
-    ].
-    ('DUdu' includes:char) ifTrue:[
-        final value:(Integer readFrom:data)
-    ].
-    ('FEGfeg' includes:char) ifTrue:[
-        final value:(Float readFrom:data)
-    ].
-    ('Oo' includes:char) ifTrue:[
-        final value:(Integer readFrom:data radix:8)
-    ].
-    ('Xx' includes:char) ifTrue:[
-        final value:(Integer readFrom:data radix:16)
-    ]
-! !
-
-!String methodsFor:'converting'!
-
-sscanf:string 
-    "Return a Collection of objects found in <string> as
-     interpreted according to the receiver. 
-     The receiver is assumed to be a conversion control string as
-     specified in the Unix C-language manual page for scanf(3).
-     For copyright information, see goodies/String-printf_scanf.chg"
-    
-    ^ self scanf:(ReadStream on:string)
-
-    "
-     '%d %x' sscanf:'1234 ff00'    
-    "
-! !
-