PrintfScanf.st
author Stefan Vogel <sv@exept.de>
Tue, 24 Mar 2020 11:09:20 +0100
changeset 5470 416a04cb68ba
parent 5361 2c50d797336c
permissions -rw-r--r--
#QUALITY by stefan class: ZipArchive added: #printOn:

"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

Object subclass:#PrintfScanf
	instanceVariableNames:''
	classVariableNames:'Singleton'
	poolDictionaries:''
	category:'System-Support'
!

!PrintfScanf class methodsFor:'documentation'!

documentation
"   
    Contributed by Jan Steinman donated to the community in 1989.

    Provided AS-IS - no warranty, use at your own risk.

    Original comment:

        NAME            printf-scanf
        AUTHOR          Jan Steinman <jans@tekgvs.labs.tek.com>
        FUNCTION        printf and scanf for Smalltalk
        ST-VERSIONS     Tek 2.2.2a 4.0
        PREREQUISITES   CharacterComparing
        CONFLICTS       
        DISTRIBUTION    world
        VERSION         1.1
        DATE            Apr 1989?
        SUMMARY 

    The following methods implement printf and scanf functionality.  They
    are intended to be used to ease porting between Smalltalk and C, and
    for facilitating machine-machine communication.  They are not at all
    intended as replacements for Smalltalk's printOn: functionality.

    Jan Steinman - N7JDB
    Tektronix Electronic Systems Laboratory
    Box 500, MS 50-370, Beaverton, OR 97077
    (w)503/627-5881 (h)503/657-7703

    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)

    Caveat:
        the behavior when the format-width is less than the preferred default precision is suboptimal;
        it leads to problems when trying to format tables into columns...
        For now: always use with width.precision formats to enforce the width.
        The current behavior (generating longer strings like printf does) may change in the future.
"
!

examples
"
    self printf:'%#x %#X %03o%*.*s' arguments: #(16rABCD 16rEF 5 9 5 'ghijklmn')
            -> '0xabcd 0xEF 005    ghijk'

    self printf:'%- 10.4s%.2e' arguments: { 'abcdefghijkl' . Float pi }  
            -> ' abcd      3.14e0'
            
    self printf:'%8.3f' arguments: { 200 sqrt negated }
            -> ' -14.142'

    self printf:'%8.3f' on:Transcript arguments: { 200 sqrt negated }
    self printf:'%10.4f' on:Transcript arguments: { 200 sqrt negated }
    self printf:'%20.10f' on:Transcript arguments: { 200 sqrt negated }

    self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789f  }
    self printf:'%20.10f' on:Transcript arguments: { 1.234567890123456789q  }

    self printf:'%x' arguments: #(16r41)        -> '41' 
    self printf:'%#x' arguments: #(16r41)       -> '0x41'
    self printf:'%d' arguments: #(16r41)        -> '65'
    self printf:'%b' arguments: #(16r41)        -> '1000001'
    self printf:'%c' arguments: #(16r41)        -> 'A'
    self printf:'%c' arguments: #( $A )         -> 'A'
    self printf:'%s' arguments: #( $A )         -> 'A'
    self printf:'%s' arguments: #( 'hello' )    -> 'hello'
    self printf:'%4s' arguments: #( 'hello' )   -> 'hello'
    self printf:'%7s' arguments: #( 'hello' )   -> '  hello'

    self sscanf:'%f%2s%s%s%s' fromString: '237.0 this is a test' 
            -> OrderedCollection(237.0 'th' 'is' 'is' 'a')

    self sscanf:'%d%f%s' fromString: '25 54.32e-01 monday'
            -> OrderedCollection(25 5.432 'monday')

    self sscanf:'%f%*f %8[A-F0-9]%c%d 0x%x%f' fromString: '12.45 1048.73 AE40Z527 0x75BCD15 34' 
            -> OrderedCollection(12.45 'AE40' 'Z' 527 123456789 34.0)

    '%#x %#X %03o%*.*s' printf: #(16rABCD 16rEF 5 9 5 'ghijklmn') 
            -> '0xabcd 0xEF 005    ghijk'

    '%- 10.4s%.2e' printf: { 'abcdefghijkl' . Float pi }  
            -> ' abcd      3.14e0'

    '%8.3f' printf: { 200 sqrt negated }
            -> ' -14.142'

    '%c' printf: #(16r41)
            -> 'A'

    '%f%2s%s%s%s' sscanf: '237.0 this is a test' 
            -> OrderedCollection(237.0 'th' 'is' 'is' 'a')

    '%d%f%s' sscanf: '25 54.32e-01 monday'
            -> OrderedCollection(25 5.432 'monday')

    '%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        

    '%p\n' printf:{ 10@20 } on:Transcript        
    '%P\n' printf:{ 10@20 } on:Transcript        
    '%S\n' printf:{ 10@20 } on:Transcript        
"
!

format_printf
"
    Printf Format specifier:
    
    required: leading '%'
        optional: '-' (POSIX refers to this as the <<flags>>)
        optional: positive number or '*' (POSIX: <<width>>)
        optional: period followed by positive number or * (POSIX: <<precision>>)
        optional: an h or l to indicate size of data (POSIX: <<length>>)
        required: character describing output behavior (POSIX: <<conversion specifier>>)

    Various implementations of printf have added different functionality.

    ANSI standards up through C99:
        more flags '+' ' ' '0' '#'
        more lengths 'L' 'hh' 'll' 'j' 'z' 't'
        more conversions 'F' 'a' 'A' 'n'

    The POSIX specification of printf added:
        positional parameters to identify argument indices
        more flags ''' (single quote)
        more conversions 'C' 'S'
        clarifications regarding corner cases and 'undefined behavior'

    BSD implementations added:
        more lengths 'q'
        more conversions 'D' 'U' 'O'

    glibc (GNU) added:
        more lengths 'Z'
        more conversions 'm'

    Windows C Runtime (CRT) added:
        more lengths 'I' 'I32' 'I64' 'w'

    glibc and CRT both added length 'Z'. 
        glibc uses 'Z' for the length size_t. 
        CRT uses Z as a conversion for length-prefixed strings. 
    This implementation takes the former approach, handling 'Z' in the same way as 'z'.

    BSD and IBM C library both added 'D'. 
        BSD uses D as a conversion, namely as an alias of 'ld'. 
        IBM uses 'D' for the length for _Decimal64, a decimal floating point type, 
        in accordance with ISO/IEC TR 24732. 
    This implementation takes the former approach.

    ================================================================
    
    This implementation also adds new conversions:

        'b' and 'B' for binary (base-2) integer renderings
        'y' and 'Y' for true/false and yes/no Boolean conversions
        'J' for JSON
        'T' and 'V' for JS typeof and valueOf inspection
        'S' for store-string
        'P' for print-string

    Conversions (upper case same as lower case, except for xX):
        'a'     (not implemented) hex floating point exp form
        'b'     binary (base 2)
        'c'     character or (first char of string)
        'd'     integer
        'e'     base-10 floating point exp form (scientific)
        'f'     base-10 floating point decimal form (non-scientific)
        'g'     'e' or 'f', whichever looks more appropriate (based on value)
        'i'     integer (alias for 'd')
        'j'     (not implemented) JSON format
        'n'     (not implemented) stores number of characters written so far into arg 
        'o'     base-8 octal
        'p'     (not implemented) pointer 
        's'     string
        't'     type (i.e. class name)
        'u'     (not implemented) unsigned (negative values are converted)
        'v'     (not implemented) store string
        'x'     base-16 hex
        'X'     base-16 hex upper case

    Parameter selection (not implemented):
        <n>$    take n'th parameter

    Dynamic width/precision (consumed in order as presented):
        *       take width/parameter from next argument

    Examples:
        PrintfScanf printf:'|%d|'  arguments:{ 123 }         -> '|123|'
        PrintfScanf printf:'|%5d|' arguments:{ 123 }         -> '|  123|'
        PrintfScanf printf:'|%-5d|' arguments:{ 123 }        -> '|123  |'

        PrintfScanf printf:'|%s|'  arguments:{ 'abc' }        -> '|abc|'
        PrintfScanf printf:'|%5s|'  arguments:{ 'abc' }       -> '|  abc|'
        PrintfScanf printf:'|%*s|'  arguments:{ 5 . 'abc' }   -> '|  abc|'

        PrintfScanf printf:'|%8f|'  arguments:{ 1.234 }       -> '|   1.234|'
        PrintfScanf printf:'|%*f|'  arguments:{ 8 . 1.234 }   -> '|   1.234|'


    Negative width will fill at the right:
        PrintfScanf printf:'|%5s|'  arguments:{ 'abc' }      -> '|  abc|'
        PrintfScanf printf:'|%-5s|' arguments:{ 'abc' }      -> '|abc  |'
        PrintfScanf printf:'|%-*s|' arguments:{ 5 . 'abc' }  -> '|abc  |'
        PrintfScanf printf:'|%*s|'  arguments:{ -5 . 'abc' } -> '|abc  |'

        PrintfScanf printf:'|%*f|'  arguments:{ -8 . 1.234 }  -> '|1.234   |'
        PrintfScanf printf:'|%-8f|'  arguments:{ 1.234 }      -> '|1.234   |'
        PrintfScanf printf:'|%-*f|'  arguments:{ 8 . 1.234 }  -> '|1.234   |'
        PrintfScanf printf:'|%-*f|'  arguments:{ -8 . 1.234 } -> '|1.234   |'

    A Zero as fill character:
        PrintfScanf printf:'|%05s|'  arguments:{ 'abc' }     -> '|00abc|'
        PrintfScanf printf:'|%-05s|' arguments:{ 'abc' }     -> '|abc00|'

        PrintfScanf printf:'|%0*f|'  arguments:{ -8 . 1.234 }  -> '|1.234   |'
        PrintfScanf printf:'|%-8f|'  arguments:{ 1.234 }      -> '|1.234   |'
        PrintfScanf printf:'|%-*f|'  arguments:{ 8 . 1.234 }  -> '|1.234   |'
        PrintfScanf printf:'|%-*f|'  arguments:{ -8 . 1.234 } -> '|1.234   |'

    Case of float-format character only affects printing of Nan and infinity:
        PrintfScanf printf:'%f' argument:1.234    
        PrintfScanf printf:'%F' argument:1.234    
        PrintfScanf printf:'%f' argument:(Float NaN)    
        PrintfScanf printf:'%F' argument:(Float NaN)    
        PrintfScanf printf:'%f' argument:(Float infinity)    
        PrintfScanf printf:'%F' argument:(Float infinity)    
        PrintfScanf printf:'%f' argument:(Float negativeInfinity)    
        PrintfScanf printf:'%F' argument:(Float negativeInfinity)    
"
!

format_scanf
"
    Scanf format specifier:
    
        required: leading '%'

    ================================================================
    
    This implementation also adds new conversions:

    Conversions (upper case same as lower case):
        'b'     binary (base 2)
        'c'     character or (first char of string)
        'd'     decimal
        'e'     float
        'f'     float
        'g'     float
        'i'     integer (alias for 'd')
        'o'     base-8 octal
        's'     string
        'u'     integer
        'x'     base-16 hex
        'n'     any number

    Length prefix:

        'h'     with float formats: reads as ShortFloat
        'L'     with float formats: reads as LongFloat
        'LL'    with float formats: reads as QDouble


     '%d %x' sscanf:'1234 ff00'         -> OrderedCollection(1234 65280)
     '%d %s' sscanf:'1234 ff00'         -> OrderedCollection(1234 'ff00')
     '%d %x %b' sscanf:'1234 ff00 1001' -> OrderedCollection(1234 65280 9)

     ('%f' sscanf:'1234') first         -> 1234.0 (Float i.e. an IEEE double)
     ('%lf' sscanf:'1234') first        -> 1234.0 (Float i.e. an IEEE double)
     ('%llf' sscanf:'1234') first       -> 1234.0 (Float i.e. an IEEE double)

     ('%hf' sscanf:'1234') first        -> 1234.0 (ShortFloat i.e. an IEEE double)
     ('%Lf' sscanf:'1234') first        -> 1234.0 (LongFloat i.e. an IEEE quad)
     ('%LLf' sscanf:'1234') first       -> 1234.0 (QDouble)
"
! !

!PrintfScanf class methodsFor:'instance creation'!

new
    Singleton isNil ifTrue:[
        Singleton := self basicNew
    ].    
    ^ Singleton
! !

!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
     $%, and a complete control string is assumed available.     

     Return when the conversion control string is consumed.  
     Leave <formatStream> pointing past the last character in the conversion control string.

     This code assumes that <formatStream> 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!!!!"    

    |nextArg ljust plus pound width precision spaceIfPositive thousands
     pad char arg argString more precisionisMin
     spaceOrSignChar "space or sign character at left"
     intVal poundPrefix|

    nextArg := 
        [
            argStream atEnd ifTrue:[
                ArgumentError raiseErrorString:'not enough arguments for format string'
            ].
            argStream next
        ].

    ljust := plus := pound := spaceIfPositive := thousands := precisionisMin := false.
    poundPrefix := nil.
    width := 0.
    precision := nil.
    pad := Character space.
    char := formatStream peek.

    char isNil ifTrue:[
        ^ nil
    ].
    char == $% ifTrue:[ 
        ^ outStream nextPut: formatStream next
    ].

    "/ flag(s):
    [
        more := false.
        char == $- ifTrue:[
            ljust := true.
            pad := Character space.         "/ see unix manual: if 0 AND - appear, o is ignored
            more := true.
        ].
        char == $  ifTrue:[
            spaceIfPositive := true.
            more := true.
        ].
        char == $+ ifTrue:[
            plus := true.  
            more := true.
        ].
        char == $# ifTrue:[
            pound := true.  
            more := true.
        ].
        char == $0 ifTrue: [
            ljust ifFalse:[ pad := $0 ].    "/ see unix manual: if 0 AND - appear, o is ignored
            more := true.
        ].
        char == $' ifTrue: [
            thousands := true.
            more := true.
        ].
        "/ char == $I ifTrue: [
        "/     "/ ignored (new in glibc2.2)
        "/     more := true.
        "/ ].
        more ifTrue:[
            formatStream next.  
            char := formatStream peek.
        ].
    ] doWhile:[more].

    "/ possibly a width
    char == $* ifTrue:[
        width := nextArg value. 
        width isInteger ifFalse:[
            self error:'non integer width argument in printf'
        ].
        width < 0 ifTrue:[
            ljust := true.
            width := width negated
        ].    
        formatStream next.  
        char := formatStream peek
    ].

    char isDigit ifTrue:[
        char == $0 ifTrue: [
            ljust ifFalse:[pad := $0].  "/ see unix manual: if 0 AND - appear, o is ignored
        ].
        width := Integer readFrom:formatStream allowRadix:false onError:0.  
        char := formatStream peek
    ].

    "/ precision separator
    
    char == $. ifTrue:[
        formatStream next.  char := formatStream peek.
        char == $* ifTrue: [
            precision := nextArg value.  
            precision isInteger ifFalse:[
                self error:'non integer precision argument in printf'
            ].    
            formatStream next.
        ] ifFalse: [
            precision := Integer readFrom: formatStream.
        ].
        char := formatStream peek
    ].

    "/ length modifier(s)
    [
        more := false.
        ((char == $l) or:[char == $L]) ifTrue:[
            "Ignore long specifiers"
            more := true.
        ].
        char == $h ifTrue:[
            "Ignore half-length (short) specifier."
            more := true.
        ].
        char == $j ifTrue:[
            "Ignore intmax-length specifier."
            more := true.
        ].
        char == $t ifTrue:[
            "Ignore ptrdiff-length specifier."
            more := true.
        ].
        char == $z ifTrue:[
            "Ignore size_t-length specifier."
            more := true.
        ].
        more ifTrue:[
            formatStream next.  
            char := formatStream peek.
        ].
    ] doWhile:[more].

    ('fegFEG' includes: char) ifTrue:[
        arg := nextArg value.

        (arg isNaN or:[arg isFinite not]) ifTrue:[
            argString := arg printString.
            (char isUppercase) 
                ifTrue:[ argString := argString asUppercase ] 
                ifFalse:[ argString := argString asLowercase ].
            arg positive ifTrue:[
                plus ifTrue: [
                    argString := '+', argString
                ] ifFalse:[
                    spaceIfPositive ifTrue: [
                        argString := ' ', argString
                    ].
                ].
            ].
        ] ifFalse:[
            arg isLimitedPrecisionReal ifTrue:[
                precision := precision ? (arg class defaultPrintPrecision).
            ] ifFalse:[ 
                arg := arg asFloat.
                precision := precision ? (Float defaultPrintPrecision).
            ].    

            argString := WriteStream on:''.
            (char == $g or:[char == $G]) ifTrue: [ 
                self absPrintFloat:arg on:argString digits:(precision + 1) 
            ] ifFalse:[
                (char == $f or:[char == $F]) ifTrue: [
                    |absArg nDigits|
                    absArg := arg abs.
                    nDigits := absArg = 0 ifTrue:[1] ifFalse:[absArg log10 ceiling asInteger abs].
                    self absDecimalPrintFloat:arg on:argString digits:(precision + nDigits "+ 1")
                ] ifFalse:[
                    (char == $e or:[char == $E]) ifTrue: [
                        self absScientificPrintFloat:arg on:argString digits:(precision + 1)
                    ].
                ].
            ].
            argString := argString contents.
            arg negative ifTrue: [
                argString := '-', argString
            ] ifFalse: [
                plus ifTrue: [
                    argString := '+', argString
                ] ifFalse:[
                    spaceIfPositive 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 nextPut: pad].
        ljust ifFalse: [outStream nextPutAll: argString].
        ^ formatStream next
    ].

    char == $c ifTrue:[
        arg := nextArg value.
        arg isString ifTrue:[
            arg := arg first asString
        ] ifFalse:[    
            arg := arg asCharacter asString
        ].
    ].
        
    char == $s ifTrue:[
        "Assume the arg is a String or Symbol."
        arg := nextArg value asString
    ] ifFalse:[
        ((char == $d) or:[char == $D or:[char == $i]]) ifTrue:[
            intVal := nextArg value asInteger.
            arg := intVal abs printString.
        ] ifFalse:[
            ((char == $o) or:[char == $O]) ifTrue:[
                "/ incompatibility here: printf prints it as an unsigned in 16/32/64 bits
                "/ Q: how many bits should we use for LargeIntegers,
                "/    or should we print a sign here???
                "/ For now, the code prints a sign
                intVal := nextArg value asInteger.
                arg := intVal abs printStringRadix: 8.
                pound ifTrue: [
                    intVal ~~ 0 ifTrue:[
                        poundPrefix := '0'
                    ]
                ].
            ] ifFalse:[
                ((char == $x) or:[char == $X]) ifTrue:[
                    intVal := nextArg value asInteger.
                    arg := intVal abs printStringRadix: 16.
                    pound ifTrue: [
                        intVal ~~ 0 ifTrue:[
                            poundPrefix := ((char == $x) ifTrue:['0x'] ifFalse:['0X']).
                        ]
                    ].

                    char == $x ifTrue:[
                        "/ make it lowercase
                        arg := arg asLowercase.
"/                        1 to: arg size do: [:i |
"/                            ('ABCDEF' includes: (arg at: i)) ifTrue:[
"/                                arg at: i put: (arg at: i) asLowercase
"/                            ]
"/                        ]
                    ].
                ] ifFalse:[
                    ((char == $b) or:[char == $B]) ifTrue:[
                        intVal := nextArg value asInteger.
                        arg := intVal abs printStringRadix: 2.
                        pound ifTrue: [
                            intVal ~~ 0 ifTrue:[
                                poundPrefix := '0b'
                            ]
                        ].
                    ] ifFalse:[
                        char == $u ifTrue:[
                            "/ should we convert unsigned numbers here???
                            "/ (negatives: maybe to the next power-of-2)
                            intVal := nextArg value asInteger.
                            arg := intVal abs printString.
                        ] ifFalse:[
                            (char == $p) ifTrue:[
                                arg := nextArg value identityHash printString.
                                precisionisMin := true.
                            ] ifFalse:[
                                (char == $P) ifTrue:[
                                    arg := nextArg value printString.
                                ] ifFalse:[
                                    (char == $S) ifTrue:[
                                        arg := nextArg value storeString.
                                    ].
                                ].
                            ].
                        ].
                    ].
                ].
            ].
        ].
    ].

    arg isNil ifTrue:[
        arg := char asString.  "/ fallback for all others
    ].

    intVal notNil ifTrue:[
        "/ format is one of doixb
        intVal < 0 ifTrue: [
            spaceOrSignChar := $-
        ] ifFalse: [
            plus ifTrue: [
                spaceOrSignChar := $+
            ] ifFalse:[
                spaceIfPositive ifTrue: [
                    spaceOrSignChar := Character space
                ].
            ].
        ].
        intVal ~~ 0 ifTrue:[
            precisionisMin := true.
        ].
    ].

    poundPrefix notNil ifTrue:[
        (pad ~~ $0 or:[ljust]) ifTrue:[
            arg := poundPrefix , arg.
            poundPrefix := nil.
        ]
    ].
    spaceOrSignChar notNil ifTrue:[
        (pad ~~ $0 or:[ljust]) ifTrue:[
            arg := spaceOrSignChar , arg.
            spaceOrSignChar := nil.
        ].
    ].

    precisionisMin ifTrue:[
        precision := (precision ? 1) max:(arg size).
    ] ifFalse:[
        precision := (precision ? arg size) min:(arg size).
    ].

    ljust ifTrue: [
        precision > 0 ifTrue:[ 
            outStream nextPutAll:(arg copyTo: precision)
        ]
    ].
    spaceOrSignChar notNil ifTrue:[
        outStream nextPut:spaceOrSignChar.
        width := width - 1.
    ].
    poundPrefix notNil ifTrue:[
        outStream nextPutAll:poundPrefix.
        width := width - (poundPrefix size).
    ].
    (width - precision) timesRepeat: [outStream nextPut: pad].
    ljust ifFalse: [
        precision > 0 ifTrue:[ 
            outStream nextPutAll:(arg copyTo: precision)
        ].
    ].
    ^ formatStream next

    "Modified: / 14-07-2017 / 11:42:01 / cg"
    "Modified: / 06-06-2019 / 23:23:01 / Claus Gittinger"
!

printf:formatString argument:arg 
    "Format and print the receiver with <arg> formatted in C style, 
     as described in the UTek manual page for printf(3)."

    ^ self printf:formatString arguments:{ arg }

    "
     self printf:'%e' on:Transcript argument:(1.234 asShortFloat)
     self printf:'%e' on:Transcript argument:(1.234 asFloat)     
     self printf:'%e' on:Transcript argument:(1.234 asLongFloat) 
     self printf:'%e' on:Transcript argument:(1.234 asQDouble)   
     self printf:'%e' on:Transcript argument:(1.234 asInteger)   

     self printf:'%10e' on:Transcript argument:(1.234 asShortFloat)
     self printf:'%10e' on:Transcript argument:(1.234 asFloat)     
     self printf:'%10e' on:Transcript argument:(1.234 asLongFloat) 
     self printf:'%10e' on:Transcript argument:(1.234 asQDouble)   
     self printf:'%10e' on:Transcript argument:(1.234 asInteger)   

     self printf:'%010e' on:Transcript argument:(1.234 asInteger)   
     self printf:'%-10e' on:Transcript argument:(1.234 asInteger)   

     self printf:'%10.9f' on:Transcript argument:(1.2345 asShortFloat)
     self printf:'%10.9f' on:Transcript argument:(1.2345 asFloat)     
     self printf:'%10.9f' on:Transcript argument:(1.2345 asLongFloat) 
     self printf:'%10.9f' on:Transcript argument:(1.2345 asQDouble)   
     self printf:'%10.9f' on:Transcript argument:(1.2345 asInteger)   
    "

    "Created: / 16-06-2017 / 14:50:08 / cg"
!

printf:formatString arguments:args 
    "Format and print the receiver with <args> formatted in C style, 
     as described in the UTek manual page for printf(3)."

    |aStream|

    aStream := WriteStream on:(formatString species new:100).
    self printf:formatString on:aStream arguments:args.
    ^ aStream contents

    "
     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:'%10e' on:Transcript arguments:{ (1.234 asShortFloat) }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asFloat)      }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asLongFloat)  }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asQDouble)    }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asInteger)    }

     self printf:'%010e' on:Transcript arguments:{ (1.234 asInteger)    }
     self printf:'%-10e' on:Transcript arguments:{ (1.234 asInteger)    }

     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asShortFloat) }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asFloat)      }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asLongFloat)  }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asQDouble)    }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asInteger)    }
    "

    "Modified: / 19-06-2017 / 15:21:34 / cg"
!

printf:formatString on:outStream argument: arg
    "Format and print formatString on <outStream> with <arg>
     formatted in C style, as described in the UTek manual page for
     printf(3)."     

    ^ self printf:formatString on:outStream arguments:{ arg }

    "
     self printf:'%e' on:Transcript argument:(1.234 asShortFloat). Transcript cr.
     self printf:'%e' on:Transcript argument:(1.234 asFloat)     . Transcript cr.
     self printf:'%e' on:Transcript argument:(1.234 asLongFloat) . Transcript cr.
     self printf:'%e' on:Transcript argument:(1.234 asQDouble)   . Transcript cr.
     self printf:'%e' on:Transcript argument:(1.234 asInteger)   . Transcript cr.

     self printf:'%10e' on:Transcript argument:(1.234 asShortFloat). Transcript cr.
     self printf:'%10e' on:Transcript argument:(1.234 asFloat)     . Transcript cr.
     self printf:'%10e' on:Transcript argument:(1.234 asLongFloat) . Transcript cr.
     self printf:'%10e' on:Transcript argument:(1.234 asQDouble)   . Transcript cr.
     self printf:'%10e' on:Transcript argument:(1.234 asInteger)   . Transcript cr.

     self printf:'%010e' on:Transcript argument:(1.234 asInteger)  . Transcript cr.
     self printf:'%-10e' on:Transcript argument:(1.234 asInteger)  . Transcript cr.

     self printf:'%10.9f' on:Transcript argument:(1.2345 asShortFloat). Transcript cr.
     self printf:'%10.9f' on:Transcript argument:(1.2345 asFloat)     . Transcript cr.
     self printf:'%10.9f' on:Transcript argument:(1.2345 asLongFloat) . Transcript cr.
     self printf:'%10.9f' on:Transcript argument:(1.2345 asQDouble)   . Transcript cr.
     self printf:'%10.9f' on:Transcript argument:(1.2345 asInteger)   . Transcript cr.
    "

    "Created: / 16-06-2017 / 14:50:40 / cg"
    "Modified (comment): / 19-06-2017 / 15:07:22 / 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)."     

    | argStream formatStream char escChar |

    argStream := ReadStream on: args.
    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:formatStream to:outStream arguments:argStream
        ]
    ]

    "
     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)      }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asLongFloat)  }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asQDouble)    }
     self printf:'%10e' on:Transcript arguments:{ (1.234 asInteger)    }

     self printf:'%010e' on:Transcript arguments:{ (1.234 asInteger)    }
     self printf:'%-10e' on:Transcript arguments:{ (1.234 asInteger)    }

     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asShortFloat) }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asFloat)      }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asLongFloat)  }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asQDouble)    }
     self printf:'%10.9f' on:Transcript arguments:{ (1.2345 asInteger)    }
    "

    "Modified (comment): / 19-06-2017 / 15:49:10 / cg"
! !

!PrintfScanf class methodsFor:'private 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\n' on:Transcript arguments: { 1.234567890123456789f  }
     self printf:'%20.10f\n' on:Transcript arguments: { 1.234567890123456789q  }

     self printf:'%20.10f\n' on:Transcript arguments: { 1e1000  }   
     self printf:'%20.10f\n' on:Transcript arguments: { 1e1000 asShortFloat }
     self printf:'%20.10f\n' on:Transcript arguments: { 1e1000 asLongFloat }
     self printf:'%20.10f\n' on:Transcript arguments: { 1e1000 asQDouble }
     self printf:'%20.10f\n' on:Transcript arguments: { 1e1000 asQuadFloat }

     self printf:'%20.10f\n' on:Transcript arguments: { 0.0   }
     self printf:'%20.10f\n' on:Transcript arguments: { 0.0 asShortFloat   }
     self printf:'%20.10f\n' on:Transcript arguments: { 0.0 asLongFloat   }
     self printf:'%20.10f\n' on:Transcript arguments: { 0.0 asQDouble   }

     self printf:'%20.10f\n' on:Transcript arguments: { Float NaN   }
     self printf:'%20.10f\n' on:Transcript arguments: { DomainError ignoreIn:[ -1.0 log10 ]   }
     self printf:'%20.10f\n' on:Transcript arguments: { DomainError ignoreIn:[ -1.0 asShortFloat log10 ]  }
     self printf:'%20.10f\n' on:Transcript arguments: { DomainError ignoreIn:[ -1.0 asLongFloat log10]   }
     self printf:'%20.10f\n' on:Transcript arguments: { DomainError ignoreIn:[ -1.0 asQDouble log10]   }

     self printf:'%10s\n' on:Transcript arguments:{ 'hello' }
     self printf:'%*s\n' on:Transcript arguments:{ 10 . 'hello' }
    "

    |absVal exp x fuzz i|

    aFloat isNaN ifTrue:[
        aStream nextPutAll:'NAN'.
        ^ self.
    ].
    aFloat isInfinite ifTrue:[
        aStream nextPutAll:'INF'.
        ^ self.
    ].
    aFloat isZero ifTrue:[
        aStream nextPutAll:'0.0'.
        ^ self.
    ].
"/    (aFloat isFloat or:[aFloat isShortFloat]) ifTrue:[
"/        thisContext isRecursive ifFalse:[
"/            aStream nextPutAll:(aFloat printfPrintString:('%',digits printString,'f')).
"/            ^ self.
"/        ].
"/    ].

    absVal := aFloat abs.

    "x is myself normalized to (1.0, 10.0), exp is my exponent"
    exp := absVal < 1.0 
            ifTrue:[ (10.0 / absVal asFloat) log10 floor negated ] 
            ifFalse:[ absVal asFloat log10 floor].

    exp := exp 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.
        i := i asInteger.
        aStream nextPut:($0 + i).
        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: / 03-07-2017 / 14:13:31 / cg"
!

absPrintFloat:aFloat on:aStream digits:digits 
    "Place a string representation of the receiver on <aStream>,
     using <digits> significant digits."

    |absFloat|

    absFloat := aFloat abs.
    (absFloat < 1.0e6 and:[ absFloat > 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|

    aFloat isNaN ifTrue:[
        aStream nextPutAll:'NAN'.
        ^ self.
    ].
    aFloat isInfinite ifTrue:[
        aStream nextPutAll:'INF'.
        ^ self.
    ].
    absVal := aFloat abs.

    absVal isZero ifTrue:[
        aStream nextPutAll:'0.0'.
        ^ self.
    ].
"/    (aFloat isFloat or:[aFloat isShortFloat]) ifTrue:[
"/        thisContext isRecursive ifFalse:[
"/            aStream nextPutAll:(aFloat printfPrintString:('%',digits printString,'e')).
"/            ^ self.
"/        ].
"/    ].
    
    "x is myself normalized to [1.0, 10.0), exp is my exponent"
    absVal < 1.0 ifTrue:[
        exp := (10.0 / absVal) log10 floor asInteger negated
    ] ifFalse:[
        exp := absVal log10 floor asInteger
    ].
    exp == 0 ifTrue:[x := absVal] ifFalse:[x := absVal / (10.0 raisedTo:exp)].
    "round the last digit to be printed"
    fuzz := 10.0 raisedTo:1 - digits.
    fuzz = 0 ifTrue:[
        fuzz := 10.0 asLongFloat raisedTo:1 - digits. 
        fuzz = 0 ifTrue:[
            "/ self error:'too many digits'.
            "/ fuzz := (10.0 asLargeFloatPrecision:((10 raisedTo:digits) integerLog2)) 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) and:[x ~= 0] ] whileTrue:[
        "use fuzz to track significance" 
        i := x truncated.
        i := i asInteger.
        aStream nextPut:($0 + i).
        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: / 21-06-2017 / 13:29:37 / cg"
    "Modified: / 05-06-2019 / 21:42:17 / Claus Gittinger"
!

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
!

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>."

    |final width char pos data scanset exclusive return last 
     isShort isLong isLongLong isLongDouble isLongLongDouble|

    final := [:retval | 
            collection add:retval.
            data == dataStream ifFalse:[
                dataStream position:dataStream position + data position
            ].
            ^ self
        ].

    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
            ]
    ].
    
    width := 0.
    isShort := isLong := isLongLong := false.
    isLongDouble := isLongLongDouble := false.
    
    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 == $[ ifTrue:[
        "What a mess!!!!" 
        return := CharacterWriteStream on:(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
    ].
    (char == $l) ifTrue:[
        isLong := true.
        format next.
        char := format peek.
        
        (char == $l) ifTrue:[
            isLongLong := true.
            format next.
            char := format peek.
        ].    
    ].    
    (char == $h) ifTrue:[
        isShort := true.
        format next.
        char := format peek
    ].
    (char == $L) ifTrue:[
        isLongDouble := true.
        format next.
        char := format peek.
        
        (char == $L) ifTrue:[
            isLongLongDouble := true.
            format next.
            char := format peek
        ].
    ].
    ('DUdu' includes:char) ifTrue:[
        final value:(Integer readFrom:data)
    ].
    ('FEGfeg' includes:char) ifTrue:[
        (isLongLongDouble) ifTrue:[
            final value:(QDouble readFrom:data)
        ] ifFalse:[    
            (isLongDouble) ifTrue:[
                final value:(LongFloat readFrom:data)
            ] ifFalse:[
                isShort ifTrue:[
                    final value:(ShortFloat readFrom:data)
                ] ifFalse:[    
                    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)
    ].
    ('Bb' includes:char) ifTrue:[
        final value:(Integer readFrom:data radix:2)
    ].
    ('Nn' includes:char) ifTrue:[
        final value:(Number readFrom:data)
    ].

    "
     '%d %x' sscanf:'1234 ff00'
     '%d %x %b' sscanf:'1234 ff00 1001'
     
     ('%f' sscanf:'1234') first
     ('%lf' sscanf:'1234') first
     ('%llf' sscanf:'1234') first
     ('%hf' sscanf:'1234') first
     ('%Lf' sscanf:'1234') first
     ('%LLf' sscanf:'1234') first
     ('%n' sscanf:'1234') first
     ('%n' sscanf:'1234.456') first
     ('%n %n' sscanf:'1234.456 123') 
    "

    "Created: / 19-06-2017 / 15:53:28 / cg"
    "Modified (comment): / 14-07-2017 / 11:31:01 / cg"
    "Modified (comment): / 18-05-2019 / 13:08:30 / Claus Gittinger"
! !

!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.
    format := ReadStream on:formatString.
    [ format atEnd ] whileFalse:[
        char := format next.
        (char == Character space or:[ char == Character tab ]) ifTrue:[
            dataStream skipSeparators.
            format skipSeparators
        ].
        char == $% ifTrue:[
            self scanArgFrom:dataStream to:results format:format
        ] ifFalse:[
            dataStream peekFor:char
        ]
    ].
    ^ results

    "Modified: / 19-06-2017 / 15:53:04 / cg"
!

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 scanf:formatString fromStream:(ReadStream on:aString)

    "
     self sscanf:'%d %d %d' fromString:'123 45 999'
     '%d %d %d' scanf:'123 45 999'
    "

    "Modified: / 19-06-2017 / 15:53:59 / cg"
    "Modified (comment): / 18-05-2019 / 13:09:48 / Claus Gittinger"
! !

!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 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'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !