#REFACTORING by cg
authorClaus Gittinger <cg@exept.de>
Mon, 19 Jun 2017 16:52:27 +0200
changeset 4417 01b4de1f0b01
parent 4416 40f676e88785
child 4418 05f82ac9d198
#REFACTORING by cg class: PrintfScanf code duplication removed comment/format in: #scanArgFrom:to:format: #scanf:fromStream: #sscanf:fromString: changed: #absDecimalPrintFloat:on:digits: #absPrintFloat:on:digits: #absScientificPrintFloat:on:digits: #formatArgCountFor: #printArgFrom:to:arguments: #printf:arguments: #printf:on:arguments: class: PrintfScanf class added: #scanArgFrom:to:format: comment/format in: #documentation #examples #printf:on:arguments: changed: #absScientificPrintFloat:on:digits: #printArgFrom:to:arguments: #scanf:fromStream: #sscanf:fromString: category of: #absDecimalPrintFloat:on:digits: #absPrintFloat:on:digits: #absScientificPrintFloat:on:digits: #formatArgCountFor:
PrintfScanf.st
--- a/PrintfScanf.st	Mon Jun 19 15:33:45 2017 +0200
+++ b/PrintfScanf.st	Mon Jun 19 16:52:27 2017 +0200
@@ -43,6 +43,9 @@
     changes:
         slight changes to make it work with higher precision real numbers
         (i.e. asking for the precision instead of hard-coding it)
+
+        no need for the singleton - classes are already singletons ready to use exactly for that.
+        (no need to use C++/Java patterns here in Smalltalk)
 "
 !
 
@@ -104,6 +107,13 @@
 
     '%f%*f %8[A-F0-9]%c%d 0x%x%f' sscanf: '12.45 1048.73 AE40Z527 0x75BCD15 34'
             -> OrderedCollection(12.45 'AE40' 'Z' 527 123456789 34.0)
+
+    '%d\n' printf:{ 1234 } on:Transcript    
+    
+    '%f\n' printf:{ 1234.0 } on:Transcript        
+    '%f\n' printf:{ 1234.0 asShortFloat } on:Transcript        
+    '%f\n' printf:{ 1234.0 asLongFloat } on:Transcript        
+    '%f\n' printf:{ 1234.0 asQDouble } on:Transcript        
 "
 ! !
 
@@ -116,160 +126,14 @@
     ^ Singleton
 ! !
 
-!PrintfScanf class methodsFor:'helpers'!
-
-absDecimalPrintFloat:aFloat on:aStream digits:digits 
-    "Place a string representation of the receiver on <aStream>,
-     using <digits> significant digits, using decimal notation."
-    
-    "
-     self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789f  }
-     self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789q  }
-    "
-
-    |absVal exp x fuzz i|
-
-    absVal := aFloat abs.
-
-    "x is myself normalized to (1.0, 10.0), exp is my exponent"
-    exp := absVal < 1.0 
-            ifTrue:[ 
-                (10.0 / absVal) log10 floor asInteger negated ] 
-            ifFalse:[
-                absVal log10 floor asInteger].
-    x := absVal / (10.0 raisedTo:exp).
-    fuzz := 10.0 raisedTo:1 - digits.
-    "round the last digit to be printed"
-    x := 0.5 * fuzz + x.
-    x >= 10.0 ifTrue:[ 
-        "check if rounding has unnormalized x" 
-        x := x / 10.0.
-        exp := exp + 1
-    ].
-    
-    exp < 0 ifTrue:[
-        1 to:(1 - exp) do:[:j | 
-            "/ cg: huh - what sort of code is that????
-            "/ aStream nextPut:('0.000000000000' at:j)
-            aStream nextPut:(j == 2 ifTrue:[$.] ifFalse:[$0])
-        ].
-        
-    ].
-    [ x >= fuzz ] whileTrue:[ 
-        "use fuzz to track significance" 
-        i := x truncated asInteger.
-        aStream nextPut:(48 + i) asCharacter.
-        x := (x - i) * 10.0.
-        fuzz := fuzz * 10.0.
-        exp := exp - 1.
-        exp = -1 ifTrue:[
-            aStream nextPut:$.
-        ]
-    ].
-    [ exp >= -1 ] whileTrue:[
-        aStream nextPut:$0.
-        exp := exp - 1.
-        exp = -1 ifTrue:[
-            aStream nextPut:$.
-        ]
-    ]
-
-    "Modified (comment): / 19-06-2017 / 14:56:40 / cg"
-!
-
-absPrintFloat:aFloat on:aStream digits:digits 
-    "Place a string representation of the receiver on <aStream>,
-     using <digits> significant digits."
-    
-    (aFloat < 1.0e6 and:[ aFloat > 1.0e-4 ]) ifTrue:[
-        self absDecimalPrintFloat:aFloat on:aStream digits:digits
-    ] ifFalse:[
-        self absScientificPrintFloat:aFloat on:aStream digits:digits
-    ]
-
-    "Modified: / 19-06-2017 / 15:03:40 / cg"
-!
-
-absScientificPrintFloat:aFloat on:aStream digits:digits 
-    "Place a string representation of the receiver on <aStream>,
-     using <digits> significant digits, using scientific notation."
-    
-    |absVal exp fuzz x q i|
-
-    absVal := aFloat abs.
-    
-    "x is myself normalized to [1.0, 10.0), exp is my exponent"
-    exp := absVal < 1.0 
-                ifTrue:[
-                    (10.0 / absVal) log10 floor asInteger negated]
-                ifFalse:[
-                    absVal log10 floor asInteger].
-    x := absVal / (10.0 raisedTo:exp).
-    "round the last digit to be printed"
-    fuzz := 10.0 raisedTo:1 - digits.
-    x := 0.5 * fuzz + x.
-    x >= 10.0 ifTrue:[ "check if rounding has unnormalized x" 
-        x := x / 10.0.
-        exp := exp + 1
-    ].
-    q := exp.
-    exp := 0.
-    [ x >= fuzz ] whileTrue:[
-        "use fuzz to track significance" 
-        i := x truncated.
-        aStream nextPut:(48 + i) asCharacter.
-        x := (x - i) * 10.0.
-        fuzz := fuzz * 10.0.
-        exp := exp - 1.
-        exp = -1 ifTrue:[
-            aStream nextPut:$.
-        ]
-    ].
-    [ exp >= -1 ] whileTrue:[
-        aStream nextPut:$0.
-        exp := exp - 1.
-        exp = -1 ifTrue:[
-            aStream nextPut:$.
-        ]
-    ].
-    aStream nextPut:$e.
-    q printOn:aStream
-
-    "Modified (comment): / 19-06-2017 / 14:58:53 / cg"
-!
-
-formatArgCountFor:aFormatString
-    "Return the number of arguments required/produced,
-     if the argument is interpreted as a printf/scanf format control string."
-
-    |nonConsecutive count|
-
-    nonConsecutive := true.
-    count := 0.
-    aFormatString do:[:c |
-        c == $% ifTrue:[
-            nonConsecutive ifTrue:[
-                count := count + 1. 
-                nonConsecutive := false
-            ] ifFalse:[
-                count := count - 1. 
-                nonConsecutive := true
-            ]
-        ] ifFalse:[
-            nonConsecutive := true
-        ]
-    ].
-    ^ count
-! !
-
 !PrintfScanf class methodsFor:'printing'!
 
 printArgFrom:formatStream to:outStream arguments:argStream
     "Interpret the required number of arguments from <argStream>
-     according to the formatting information in <formatStream>.  Place
-     the interpretation on <outStream>.  The interpretation is C
-     printf(3) style, as described in the UTek manual page for
-     printf(3).  <formatStream> is assumed to be positioned just past
+     according to the formatting information in <formatStream>.  
+     Place the interpretation on <outStream>.  
+     The interpretation is C printf(3) style, as described in the UTek manual page for printf(3).  
+     <formatStream> is assumed to be positioned just past
      $%, and a complete control string is assumed available.     
 
      Return when the conversion control string is consumed.  
@@ -281,7 +145,14 @@
      argument types do not match conversion codes, but it probably
      won't dump core, like C does in such cases!!!!"    
 
-    | ljust plus pound width precision pad char arg argString |
+    |nextArg ljust plus pound width precision pad char arg argString |
+
+    nextArg := [
+                    argStream atEnd ifTrue:[
+                        self error:'not enough arguments for format string'
+                    ].
+                    argStream next
+               ].
 
     ljust := plus := pound := false.
     width := 0.
@@ -319,7 +190,7 @@
     ].
 
     char == $* ifTrue:[
-        width := argStream next.  
+        width := nextArg value.  
         formatStream next.  
         char := formatStream peek
     ].
@@ -333,7 +204,7 @@
     char == $. ifTrue:[
         formatStream next.  char := formatStream peek.
         char == $*
-            ifTrue: [precision := argStream next.  formatStream next.]
+            ifTrue: [precision := nextArg value.  formatStream next.]
             ifFalse: [precision := Integer readFrom: formatStream.].
         char := formatStream peek
     ].
@@ -344,7 +215,7 @@
     ].
 
     ('feg' includes: char) ifTrue:[
-        arg := argStream next.
+        arg := nextArg value.
         arg isLimitedPrecisionReal ifTrue:[
             precision := precision ? (arg class defaultPrintPrecision).
         ] ifFalse:[ 
@@ -381,34 +252,34 @@
     ].
 
     char == $c ifTrue:[
-        arg := argStream next asCharacter asString
+        arg := nextArg value asCharacter asString
     ].
         
     char == $s ifTrue:[
         "Assume the arg is a String or Symbol."
-        arg := argStream next asString
+        arg := nextArg value asString
     ].
 
     char == $d ifTrue:[
-        arg := argStream next asInteger printString.
+        arg := nextArg value asInteger printString.
         plus ifTrue: [arg := '+', arg]
     ].
 
     char == $u ifTrue:[
-        arg := argStream next asInteger abs printString
+        arg := nextArg value asInteger abs printString
     ].
 
     char == $o ifTrue:[
-        arg := argStream next asInteger abs printStringRadix: 8.
+        arg := nextArg value asInteger abs printStringRadix: 8.
         pound ifTrue: [arg := '0', arg]
     ].
 
     ('xX' includes: char) ifTrue:[
-        arg := argStream next asInteger abs printStringRadix: 16.
+        arg := nextArg value asInteger abs printStringRadix: 16.
         pound ifTrue: [arg := '0x', arg]
     ].
     ('bB' includes: char) ifTrue:[
-        arg := argStream next asInteger abs printStringRadix: 2.
+        arg := nextArg value asInteger abs printStringRadix: 2.
         pound ifTrue: [arg := '0b', arg]
     ].
 
@@ -426,7 +297,7 @@
     ljust ifFalse: [outStream nextPutAll: (arg copyFrom: 1 to: precision)].
     ^ formatStream next
 
-    "Modified (comment): / 19-06-2017 / 15:20:11 / cg"
+    "Modified (comment): / 19-06-2017 / 15:46:33 / cg"
 !
 
 printf:formatString argument:arg 
@@ -536,24 +407,37 @@
      formatted in C style, as described in the UTek manual page for
      printf(3)."     
 
-    | argStream inStream char |
+    | argStream formatStream char escChar |
 
     argStream := ReadStream on: args.
-    inStream := ReadStream on: aFormatString.
-    [inStream atEnd] whileFalse:[
-        (char := inStream next) == $% ifFalse: [
-            outStream nextPut: char
+    formatStream := ReadStream on: aFormatString.
+    [formatStream atEnd] whileFalse:[
+        (char := formatStream next) == $% ifFalse: [
+            char == $\ ifTrue:[
+                escChar := formatStream next.
+                escChar == $n ifTrue:[ char := Character nl ]
+                ifFalse:[ escChar == $t ifTrue:[ char := Character tab ]
+                ifFalse:[ escChar == $r ifTrue:[ char := Character return ]
+                ifFalse:[ char := escChar ]]]
+            ].        
+            outStream nextPut:char
         ] ifTrue: [
-            self printArgFrom:inStream to:outStream arguments:argStream
+            self printArgFrom:formatStream to:outStream arguments:argStream
         ]
     ]
 
     "
-     self printf:'%e' on:Transcript arguments:{ (1.234 asShortFloat) }
-     self printf:'%e' on:Transcript arguments:{ (1.234 asFloat)      }
-     self printf:'%e' on:Transcript arguments:{ (1.234 asLongFloat)  }
-     self printf:'%e' on:Transcript arguments:{ (1.234 asQDouble)    }
-     self printf:'%e' on:Transcript arguments:{ (1.234 asInteger)    }
+     self printf:'%e\n' on:Transcript arguments:{ (1.234 asShortFloat) }
+     self printf:'%f\n' on:Transcript arguments:{ (1.234 asShortFloat) }
+     self printf:'%g\n' on:Transcript arguments:{ (1.234 asShortFloat) }
+
+     self printf:'%e\n' on:Transcript arguments:{ (1.234 asFloat)      }
+     self printf:'%f\n' on:Transcript arguments:{ (1.234 asFloat)      }
+     self printf:'%g\n' on:Transcript arguments:{ (1.234 asFloat)      }
+
+     self printf:'%e\n' on:Transcript arguments:{ (1.234 asLongFloat)  }
+     self printf:'%e\n' on:Transcript arguments:{ (1.234 asQDouble)    }
+     self printf:'%e\n' on:Transcript arguments:{ (1.234 asInteger)    }
 
      self printf:'%10e' on:Transcript arguments:{ (1.234 asShortFloat) }
      self printf:'%10e' on:Transcript arguments:{ (1.234 asFloat)      }
@@ -571,78 +455,155 @@
      self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asInteger)    }
     "
 
-    "Modified: / 19-06-2017 / 15:21:07 / cg"
+    "Modified (comment): / 19-06-2017 / 15:49:10 / cg"
 ! !
 
-!PrintfScanf class methodsFor:'scanning'!
+!PrintfScanf class methodsFor:'private helpers'!
 
-scanf:formatString fromStream: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 UTek manual page for scanf(3)."
+absDecimalPrintFloat:aFloat on:aStream digits:digits 
+    "Place a string representation of the receiver on <aStream>,
+     using <digits> significant digits, using decimal notation."
+    
+    "
+     self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789f  }
+     self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789q  }
+    "
 
-   ^ self new scanf:formatString fromStream:dataStream
-!
+    |absVal exp x fuzz i|
+
+    absVal := aFloat abs.
 
-sscanf:formatString fromString:aString 
-    "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
-     UTek manual page for scanf(3)."
-
-   ^ self new sscanf:formatString fromString:aString
-! !
+    "x is myself normalized to (1.0, 10.0), exp is my exponent"
+    exp := absVal < 1.0 
+            ifTrue:[ 
+                (10.0 / absVal) log10 floor asInteger negated ] 
+            ifFalse:[
+                absVal log10 floor asInteger].
+    x := absVal / (10.0 raisedTo:exp).
+    fuzz := 10.0 raisedTo:1 - digits.
+    "round the last digit to be printed"
+    x := 0.5 * fuzz + x.
+    x >= 10.0 ifTrue:[ 
+        "check if rounding has unnormalized x" 
+        x := x / 10.0.
+        exp := exp + 1
+    ].
+    
+    exp < 0 ifTrue:[
+        1 to:(1 - exp) do:[:j | 
+            "/ cg: huh - what sort of code is that????
+            "/ aStream nextPut:('0.000000000000' at:j)
+            aStream nextPut:(j == 2 ifTrue:[$.] ifFalse:[$0])
+        ].
+        
+    ].
+    [ x >= fuzz ] whileTrue:[ 
+        "use fuzz to track significance" 
+        i := x truncated asInteger.
+        aStream nextPut:(48 + i) asCharacter.
+        x := (x - i) * 10.0.
+        fuzz := fuzz * 10.0.
+        exp := exp - 1.
+        exp = -1 ifTrue:[
+            aStream nextPut:$.
+        ]
+    ].
+    [ exp >= -1 ] whileTrue:[
+        aStream nextPut:$0.
+        exp := exp - 1.
+        exp = -1 ifTrue:[
+            aStream nextPut:$.
+        ]
+    ]
 
-!PrintfScanf methodsFor:'helpers'!
-
-absDecimalPrintFloat:arg1 on:arg2 digits:arg3
-    ^ self class absDecimalPrintFloat:arg1 on:arg2 digits:arg3
-!
-
-absPrintFloat:arg1 on:arg2 digits:arg3
-    ^ self class absPrintFloat:arg1 on:arg2 digits:arg3
+    "Modified (comment): / 19-06-2017 / 14:56:40 / cg"
 !
 
-absScientificPrintFloat:arg1 on:arg2 digits:arg3
-    ^ self class absScientificPrintFloat:arg1 on:arg2 digits:arg3
-!
+absPrintFloat:aFloat on:aStream digits:digits 
+    "Place a string representation of the receiver on <aStream>,
+     using <digits> significant digits."
+    
+    (aFloat < 1.0e6 and:[ aFloat > 1.0e-4 ]) ifTrue:[
+        self absDecimalPrintFloat:aFloat on:aStream digits:digits
+    ] ifFalse:[
+        self absScientificPrintFloat:aFloat on:aStream digits:digits
+    ]
 
-formatArgCountFor:arg
-    ^ self class formatArgCountFor:arg
-! !
-
-!PrintfScanf methodsFor:'printing'!
-
-printArgFrom:arg1 to:arg2 arguments:arg3
-    ^ self class printArgFrom:arg1 to:arg2 arguments:arg3
+    "Modified: / 19-06-2017 / 15:03:40 / cg"
 !
 
-printf:aString arguments:args 
-    "Format and print the receiver with <args> formatted in C style, 
-     as described in the UTek manual page for printf(3).
-     Returns the formatted printString."
+absScientificPrintFloat:aFloat on:aStream digits:digits 
+    "Place a string representation of the receiver on <aStream>,
+     using <digits> significant digits, using scientific notation."
+    
+    |absVal exp fuzz x q i|
+
+    absVal := aFloat abs.
     
-    ^ self class printf:aString arguments:args
+    "x is myself normalized to [1.0, 10.0), exp is my exponent"
+    exp := absVal < 1.0 
+                ifTrue:[
+                    (10.0 / absVal) log10 floor asInteger negated]
+                ifFalse:[
+                    absVal log10 floor asInteger].
+    x := absVal / (10.0 raisedTo:exp).
+    "round the last digit to be printed"
+    fuzz := 10.0 raisedTo:1 - digits.
+    x := 0.5 * fuzz + x.
+    x >= 10.0 ifTrue:[ "check if rounding has unnormalized x" 
+        x := x / 10.0.
+        exp := exp + 1
+    ].
+    q := exp.
+    exp := 0.
+    [ x >= fuzz ] whileTrue:[
+        "use fuzz to track significance" 
+        i := x truncated.
+        i := i asInteger.
+        aStream nextPut:(48 + i) asCharacter.
+        x := (x - i) * 10.0.
+        fuzz := fuzz * 10.0.
+        exp := exp - 1.
+        exp = -1 ifTrue:[
+            aStream nextPut:$.
+        ]
+    ].
+    [ exp >= -1 ] whileTrue:[
+        aStream nextPut:$0.
+        exp := exp - 1.
+        exp = -1 ifTrue:[
+            aStream nextPut:$.
+        ]
+    ].
+    aStream nextPut:$e.
+    q printOn:aStream
 
-    "
-     self new printf:'%d %x' arguments:#(1234 45054) 
-    "
-
-    "Modified: / 19-06-2017 / 15:21:56 / cg"
+    "Modified: / 19-06-2017 / 15:57:09 / cg"
 !
 
-printf:aFormatString on:outStream arguments: args
-    "Format and print aFormatString on <outStream> with <args>
-     formatted in C style, as described in the UTek manual page for
-     printf(3)."     
+formatArgCountFor:aFormatString
+    "Return the number of arguments required/produced,
+     if the argument is interpreted as a printf/scanf format control string."
+
+    |nonConsecutive count|
 
-    self class printf:aFormatString on:outStream arguments: args
-
-    "Modified (comment): / 19-06-2017 / 15:22:15 / cg"
-! !
-
-!PrintfScanf methodsFor:'scanning'!
+    nonConsecutive := true.
+    count := 0.
+    aFormatString do:[:c |
+        c == $% ifTrue:[
+            nonConsecutive ifTrue:[
+                count := count + 1. 
+                nonConsecutive := false
+            ] ifFalse:[
+                count := count - 1. 
+                nonConsecutive := true
+            ]
+        ] ifFalse:[
+            nonConsecutive := true
+        ]
+    ].
+    ^ count
+!
 
 scanArgFrom:dataStream to:collection format:format 
     "Add to <collection> an object who's representation is found
@@ -656,7 +617,7 @@
      control string, leave <dataStream> pointing past any width
      specified in <format>, or at the first character that doesn't
      make sense for the <format>."
-    
+
     |final width char pos data scanset exclusive return last|
 
     final := [:retval | 
@@ -753,15 +714,17 @@
         final value:(Integer readFrom:data radix:2)
     ].
 
-    "Modified: / 29-11-2011 / 11:55:32 / cg"
-!
+    "Created: / 19-06-2017 / 15:53:28 / cg"
+! !
+
+!PrintfScanf class methodsFor:'scanning'!
 
 scanf:formatString fromStream: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 UTek manual page for scanf(3)."
-    
+
     |results format char|
 
     results := OrderedCollection new.
@@ -780,7 +743,7 @@
     ].
     ^ results
 
-    "Modified (format): / 19-06-2017 / 15:22:46 / cg"
+    "Modified: / 19-06-2017 / 15:53:04 / cg"
 !
 
 sscanf:formatString fromString:aString 
@@ -788,12 +751,118 @@
      interpreted according to the receiver.  The receiver is
      assumed to be a conversion control string as specified in the
      UTek manual page for scanf(3)."
+
+    ^ self scanf:formatString fromStream:(ReadStream on:aString)
+
+    "Modified: / 19-06-2017 / 15:53:59 / cg"
+! !
+
+!PrintfScanf methodsFor:'helpers'!
+
+absDecimalPrintFloat:arg1 on:arg2 digits:arg3
+    <resource: #obsolete>
+    ^ self class absDecimalPrintFloat:arg1 on:arg2 digits:arg3
+!
+
+absPrintFloat:arg1 on:arg2 digits:arg3
+    <resource: #obsolete>
+    ^ self class absPrintFloat:arg1 on:arg2 digits:arg3
+!
+
+absScientificPrintFloat:arg1 on:arg2 digits:arg3
+    <resource: #obsolete>
+    ^ self class absScientificPrintFloat:arg1 on:arg2 digits:arg3
+!
+
+formatArgCountFor:arg
+    <resource: #obsolete>
+    ^ self class formatArgCountFor:arg
+! !
+
+!PrintfScanf methodsFor:'printing'!
+
+printArgFrom:arg1 to:arg2 arguments:arg3
+    <resource: #obsolete>
+    ^ self class printArgFrom:arg1 to:arg2 arguments:arg3
+!
+
+printf:aString arguments:args
+    <resource: #obsolete>
+ 
+    "Format and print the receiver with <args> formatted in C style, 
+     as described in the UTek manual page for printf(3).
+     Returns the formatted printString."
     
-    ^ self scanf:formatString fromStream:(ReadStream on:aString)
+    ^ self class printf:aString arguments:args
+
+    "
+     self new printf:'%d %x' arguments:#(1234 45054) 
+    "
+
+    "Modified: / 19-06-2017 / 15:21:56 / cg"
+!
+
+printf:aFormatString on:outStream arguments: args
+    <resource: #obsolete>
+    "Format and print aFormatString on <outStream> with <args>
+     formatted in C style, as described in the UTek manual page for
+     printf(3)."     
+
+    self class printf:aFormatString on:outStream arguments: args
+
+    "Modified (comment): / 19-06-2017 / 15:22:15 / cg"
+! !
+
+!PrintfScanf methodsFor:'scanning'!
+
+scanArgFrom:dataStream to:collection format:format
+    <resource: #obsolete>
+ 
+    "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>."
+    
+    ^ self class scanArgFrom:dataStream to:collection format:format
+
+    "Modified: / 19-06-2017 / 15:54:43 / cg"
+!
+
+scanf:formatString fromStream:dataStream
+    <resource: #obsolete>
+ 
+    "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 UTek manual page for scanf(3)."
+    
+    ^ self class scanf:formatString fromStream:dataStream
+
+    "Modified: / 19-06-2017 / 15:54:27 / cg"
+!
+
+sscanf:formatString fromString:aString
+    <resource: #obsolete>
+ 
+    "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
+     UTek manual page for scanf(3)."
+    
+    ^ self class sscanf:formatString fromString:aString
 
     "
      self new sscanf:'%d %x' fromString:'1234 affe'
     "
+
+    "Modified: / 19-06-2017 / 15:54:14 / cg"
 ! !
 
 !PrintfScanf class methodsFor:'documentation'!