extensions.st
changeset 2303 74c77b8cf160
parent 2295 27e3885efddd
child 2337 755696d72648
--- a/extensions.st	Thu Oct 08 10:39:16 2009 +0200
+++ b/extensions.st	Fri Oct 09 18:27:07 2009 +0200
@@ -6,54 +6,54 @@
 asKoelnerPhoneticCode
     "return a koelner phonetic code.
      The koelnerPhonetic code is for the german language what the soundex code is for english;
-     it returns simular strings for similar sounding words. 
-     There are some differences to soundex, though: 
-        its length is not limited to 4, but depends on the length of the original string;
-        it does not start with the first character of the input.
+     it returns simular strings for similar sounding words.
+     There are some differences to soundex, though:
+	its length is not limited to 4, but depends on the length of the original string;
+	it does not start with the first character of the input.
 
      Caveat: this phonetic code is especially suited for german words.
-             Please have a look at the other phonetic comparison operators found    
-             in PhoneticStringUtilities."
+	     Please have a look at the other phonetic comparison operators found
+	     in PhoneticStringUtilities."
 
-    ^ PhoneticStringUtilities koelnerPhoneticCodeOf:self 
+    ^ PhoneticStringUtilities koelnerPhoneticCodeOf:self
 
     "
      #(
-        'Müller'
-        'Miller'
-        'Mueller'
-        'Mühler'
-        'Mühlherr'
-        'Mülherr'
-        'Myler'
-        'Millar'
-        'Myller'
-        'Müllar'
-        'Müler'
-        'Muehler'
-        'Mülller'
-        'Müllerr'
-        'Muehlherr'
-        'Muellar'
-        'Mueler'
-        'Mülleer'
-        'Mueller'
-        'Nüller'
-        'Nyller'
-        'Niler'
-        'Czerny'
-        'Tscherny'
-        'Czernie'
-        'Tschernie'
-        'Schernie'
-        'Scherny'
-        'Scherno'
-        'Czerne'
-        'Zerny'
-        'Tzernie'
-        'Breschnew'
+	'Müller'
+	'Miller'
+	'Mueller'
+	'Mühler'
+	'Mühlherr'
+	'Mülherr'
+	'Myler'
+	'Millar'
+	'Myller'
+	'Müllar'
+	'Müler'
+	'Muehler'
+	'Mülller'
+	'Müllerr'
+	'Muehlherr'
+	'Muellar'
+	'Mueler'
+	'Mülleer'
+	'Mueller'
+	'Nüller'
+	'Nyller'
+	'Niler'
+	'Czerny'
+	'Tscherny'
+	'Czernie'
+	'Tschernie'
+	'Schernie'
+	'Scherny'
+	'Scherno'
+	'Czerne'
+	'Zerny'
+	'Tzernie'
+	'Breschnew'
      ) do:[:w |
-         Transcript show:w; show:'->'; showCR:(w asKoelnerPhoneticCode)
+	 Transcript show:w; show:'->'; showCR:(w asKoelnerPhoneticCode)
      ].
     "
 
@@ -77,13 +77,13 @@
      (read Knuth or search the web if you dont know what a soundex code is).
 
      Caveat: 'similar sounding words' means: 'similar sounding in english'
-             Please have a look at the other phonetic comparison operators found    
-             in PhoneticStringUtilities."
+	     Please have a look at the other phonetic comparison operators found
+	     in PhoneticStringUtilities."
 
     ^ PhoneticStringUtilities soundexCodeOf:self
 
     "
-     'claus' asSoundexCode     
+     'claus' asSoundexCode
      'clause' asSoundexCode
      'close' asSoundexCode
      'smalltalk' asSoundexCode
@@ -101,13 +101,13 @@
 
 !CharacterArray methodsFor:'printing & storing'!
 
-printf:args 
-    "Format and print the receiver with <args> formatted in C style, 
+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).
      Return the resulting string.
 
      For copyright information, see goodies/String-printf_scanf.chg"
-    
+
     |aStream|
 
     aStream := WriteStream on:String new.
@@ -115,18 +115,18 @@
     ^ aStream contents
 
     "
-     Transcript showCR:('%05x %d %f %o' printf:{ 123. 234*5. 1.234. 8r377 } ) 
+     Transcript showCR:('%05x %d %f %o' printf:{ 123. 234*5. 1.234. 8r377 } )
     "
 
     "
      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 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 show: ('%- 10.4s%.2e' printf: (Array with: 'abcdefghijkl' with: Float pi)).
      Transcript showCR: '.'
 
      Transcript show: '''%8.3f'' printf: (Array with: 200 sqrt negated) = .'.
@@ -155,76 +155,76 @@
      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
-        ]
+	(char := inStream next) == $% ifFalse:[
+	    outStream nextPut:char
+	] ifTrue:[
+	    self
+		printf_printArgFrom:inStream
+		to:outStream
+		withData:argStream
+	]
     ]
 ! !
 
 !CharacterArray methodsFor:'printing & storing'!
 
-printfWith:arg1 
+printfWith:arg1
     "Format and print the receiver with <arg1> formatted in C style,
      as specified in the Unix C-language manual page for printf(3).
      Return the resulting string."
-    
+
     ^ self printf:(Array with:arg1)
 
     "
-     Transcript showCR:('%05x' printfWith:123) 
+     Transcript showCR:('%05x' printfWith:123)
     "
 ! !
 
 !CharacterArray methodsFor:'printing & storing'!
 
-printfWith:arg1 with:arg2 
-    "Format and print the receiver with <argI> formatted in C style, 
+printfWith:arg1 with:arg2
+    "Format and print the receiver with <argI> formatted in C style,
      as specified in the Unix C-language manual page for printf(3).
      Return the resulting string."
-    
+
     ^ self printf:(Array with:arg1 with:arg2)
 
     "
-     Transcript showCR:('%d %05x' printfWith:123 with:234) 
+     Transcript showCR:('%d %05x' printfWith:123 with:234)
     "
 ! !
 
 !CharacterArray methodsFor:'printing & storing'!
 
 printfWith:arg1 with:arg2 with:arg3
-    "Format and print the receiver with <argI> formatted in C style,  
+    "Format and print the receiver with <argI> formatted in C style,
      as specified in the Unix C-language manual page for printf(3).
      Return the resulting string."
-    
+
     ^ self printf:(Array with:arg1 with:arg2 with:arg3)
 
     "
-     Transcript showCR:('%d %05x %08o' printfWith:123 with:234 with:345) 
+     Transcript showCR:('%d %05x %08o' printfWith:123 with:234 with:345)
     "
 ! !
 
 !CharacterArray methodsFor:'printing & storing'!
 
 printfWith:arg1 with:arg2 with:arg3 with:arg4
-    "Format and print the receiver with <argI> formatted in C style,  
+    "Format and print the receiver with <argI> formatted in C style,
      as specified in the Unix C-language manual page for printf(3).
      Return the resulting string."
-    
+
     ^ self printf:(Array with:arg1 with:arg2 with:arg3 with:arg4)
 
     "
-     Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123) 
+     Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)
     "
 ! !
 
@@ -234,39 +234,39 @@
     "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
-        ]
+    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 
+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>.  
+     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.  
+     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
@@ -276,15 +276,15 @@
      won't dump core, like C does in such cases!!
 
      For copyright information, see goodies/String-printf_scanf.chg"
-    
+
     |nextArg ljust plus pound width precision pad char arg argString|
 
-    nextArg := [ 
-                    argStream atEnd ifTrue:[
-                        self error:'not enough arguments for format string'
-                    ].
-                    argStream next
-               ].
+    nextArg := [
+		    argStream atEnd ifTrue:[
+			self error:'not enough arguments for format string'
+		    ].
+		    argStream next
+	       ].
 
     ljust := plus := pound := false.
     width := 0.
@@ -292,153 +292,153 @@
     pad := $ .
     char := inStream peek.
     char == $% ifTrue:[
-        ^ outStream nextPut:inStream next
+	^ outStream nextPut:inStream next
     ].
     char == $- ifTrue:[
-        ljust := true.
-        inStream next.
-        char := inStream peek
+	ljust := true.
+	inStream next.
+	char := inStream peek
     ].
     char == $  ifTrue:[
-        outStream space.
-        inStream next.
-        char := inStream peek
+	outStream space.
+	inStream next.
+	char := inStream peek
     ].
     char == $+ ifTrue:[
-        plus := true.
-        inStream next.
-        char := inStream peek
+	plus := true.
+	inStream next.
+	char := inStream peek
     ].
     char == $# ifTrue:[
-        pound := true.
-        inStream next.
-        char := inStream peek
+	pound := true.
+	inStream next.
+	char := inStream peek
     ].
     char == $* ifTrue:[
-        width := nextArg value.
-        inStream next.
-        char := inStream peek
+	width := nextArg value.
+	inStream next.
+	char := inStream peek
     ].
     char isDigit ifTrue:[
-        char == $0 ifTrue:[
-            pad := $0
-        ].
-        width := Integer readFrom:inStream.
-        char := inStream peek
+	char == $0 ifTrue:[
+	    pad := $0
+	].
+	width := Integer readFrom:inStream.
+	char := inStream peek
     ].
     char == $. ifTrue:[
-        inStream next.
-        char := inStream peek.
-        char == $* ifTrue:[
-            precision := nextArg value.
-            inStream next.
-            char := inStream peek
-        ] ifFalse:[
-            precision := Integer readFrom:inStream.
-            char := inStream peek
-        ]
+	inStream next.
+	char := inStream peek.
+	char == $* ifTrue:[
+	    precision := nextArg value.
+	    inStream next.
+	    char := inStream peek
+	] ifFalse:[
+	    precision := Integer readFrom:inStream.
+	    char := inStream peek
+	]
     ].
     char == $l "Ignore long specifier." ifTrue:[
-        inStream next.
-        char := inStream peek
+	inStream next.
+	char := inStream peek
     ].
     ('feg' includes:char) ifTrue:[
-        arg := nextArg value 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
+	arg := nextArg value 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:nextArg value asCharacter
+	arg := String with:nextArg value asCharacter
     ].
     char == $s "Assume the arg is a String or Symbol." ifTrue:[
-        arg := nextArg value asString
+	arg := nextArg value asString
     ].
     char == $d ifTrue:[
-        arg := nextArg value asInteger printString.
-        plus ifTrue:[
-            arg := '+' , arg
-        ]
+	arg := nextArg value asInteger printString.
+	plus ifTrue:[
+	    arg := '+' , arg
+	]
     ].
     char == $u ifTrue:[
-        arg := nextArg value asInteger abs printString
+	arg := nextArg value asInteger abs printString
     ].
     char == $o ifTrue:[
-        arg := nextArg value asInteger abs printStringRadix:8.
-        pound ifTrue:[
-            arg := '0' , arg
-        ]
+	arg := nextArg value asInteger abs printStringRadix:8.
+	pound ifTrue:[
+	    arg := '0' , arg
+	]
     ].
     char == $b ifTrue:[
-        arg := nextArg value asInteger abs printStringRadix:2.
-        pound ifTrue:[
-            arg := '0' , arg
-        ]
+	arg := nextArg value asInteger abs printStringRadix:2.
+	pound ifTrue:[
+	    arg := '0' , arg
+	]
     ].
     ('xX' includes:char) ifTrue:[
-        arg := nextArg value asInteger abs printStringRadix:16.
-        pound ifTrue:[
-            arg := '0x' , arg
-        ]
+	arg := nextArg value 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
-            ]
-        ]
+	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)
+	outStream nextPutAll:(arg copyFrom:1 to:precision)
     ].
     width - precision timesRepeat:[
-        outStream nextPut:pad
+	outStream nextPut:pad
     ].
     ljust ifFalse:[
-        outStream nextPutAll:(arg copyFrom:1 to:precision)
+	outStream nextPutAll:(arg copyFrom:1 to:precision)
     ].
     ^ inStream next
 ! !
@@ -447,7 +447,7 @@
 
 printf_printOn:outStream withData:args
     <resource: #obsolete>
- 
+
     "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).
 
@@ -459,46 +459,46 @@
 
 !CharacterArray methodsFor:'converting'!
 
-scanf:dataStream 
+scanf:dataStream
     "Return a Collection of objects found in the Character Stream
-     <dataStream> as interpreted according to the receiver.  
+     <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
-        ]
+	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')    
+     '%d %x' scanf:(ReadStream on:'1234 ff00')
     "
 ! !
 
 !CharacterArray methodsFor:'private'!
 
-scanf_scanArgFrom:dataStream to:collection format:format 
+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 
+     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
@@ -508,127 +508,127 @@
      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
-        ].
+    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
+	^ dataStream peekFor:char
     ].
     char == $* ifTrue:[
-        format next.
-        char := format peek.
-        final := [:retval | 
-                data == dataStream ifFalse:[
-                    dataStream position:dataStream position + data position
-                ].
-                ^ self
-            ]
+	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
+	width := Integer readFrom:format.
+	char := format peek
     ].
     ('slhduoxfeg' includes:char) ifTrue:[
-        dataStream skipSeparators
+	dataStream skipSeparators
     ].
     width = 0 ifTrue:[
-        data := dataStream
+	data := dataStream
     ] ifFalse:[
-        pos := dataStream position.
-        data := ReadStream on:(dataStream next:width).
-        dataStream position:pos
+	pos := dataStream position.
+	data := ReadStream on:(dataStream next:width).
+	dataStream position:pos
     ].
     char == $s ifTrue:[
-        final value:(data upToSeparator)
+	final value:(data upToSeparator)
     ].
     char == $c ifTrue:[
-        width = 0 ifTrue:[
-            final value:(String with:data next)
-        ] ifFalse:[
-            final value:data contents
-        ]
+	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
+	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
+	format next.
+	char := format peek
     ].
     ('DUdu' includes:char) ifTrue:[
-        final value:(Integer readFrom:data)
+	final value:(Integer readFrom:data)
     ].
     ('FEGfeg' includes:char) ifTrue:[
-        final value:(Float readFrom:data)
+	final value:(Float readFrom:data)
     ].
     ('b' includes:char) ifTrue:[
-        final value:(Integer readFrom:data radix:2)
+	final value:(Integer readFrom:data radix:2)
     ].
     ('Oo' includes:char) ifTrue:[
-        final value:(Integer readFrom:data radix:8)
+	final value:(Integer readFrom:data radix:8)
     ].
     ('Xx' includes:char) ifTrue:[
-        final value:(Integer readFrom:data radix:16)
+	final value:(Integer readFrom:data radix:16)
     ]
 
     "
-     '%d %x' sscanf:'1234 ff00'    
-     '%d %x %b' sscanf:'1234 ff00 1001'    
+     '%d %x' sscanf:'1234 ff00'
+     '%d %x %b' sscanf:'1234 ff00 1001'
     "
 ! !
 
 !CharacterArray methodsFor:'converting'!
 
-sscanf:string 
+sscanf:string
     "Return a Collection of objects found in <string> as
-     interpreted according to the receiver. 
+     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'    
-     '%d %x %b' sscanf:'1234 ff00 1001'    
+     '%d %x' sscanf:'1234 ff00'
+     '%d %x %b' sscanf:'1234 ff00 1001'
     "
 ! !
 
 !Float methodsFor:'private'!
 
-absDecimalPrintOn:aStream digits:digits 
+absDecimalPrintOn:aStream digits:digits
     "Place a string representation of the receiver's abs value
      on <aStream> using <digits> significant digits, using decimal notation.
      This is a helper for printf."
@@ -636,94 +636,94 @@
     |exp x fuzz i|
 
     "x is myself normalized to (1.0, 10.0), exp is my exponent"
-    exp := self abs < 1.0 
-                ifTrue:[ (10.0 / self abs) log floor negated ] 
-                ifFalse:[ self abs log floor ].
+    exp := self abs < 1.0
+		ifTrue:[ (10.0 / self abs) log floor negated ]
+		ifFalse:[ self abs log floor ].
     x := self abs / (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 "check if rounding has unnormalized x" ifTrue:[
-        x := x / 10.0.
-        exp := exp + 1
+	x := x / 10.0.
+	exp := exp + 1
     ].
     exp < 0 ifTrue:[
-        1 to:1 - exp do:[:j | 
-            aStream nextPut:('0.000000000000' at:j)
-        ]
+	1 to:1 - exp do:[:j |
+	    aStream nextPut:('0.000000000000' at:j)
+	]
     ].
     [ x >= fuzz ] "use fuzz to track significance" whileTrue:[
-        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:$.
-        ]
+	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:$0.
+	exp := exp - 1.
+	exp = -1 ifTrue:[
+	    aStream nextPut:$.
+	]
     ]
 ! !
 
 !Float methodsFor:'private'!
 
-absPrintOn:aStream digits:digits 
-    "Place a string representation of the receiver's abs value on <aStream> using 
+absPrintOn:aStream digits:digits
+    "Place a string representation of the receiver's abs value on <aStream> using
      <digits> significant digits.
      This is a helper for printf."
-    
+
     (self < 1.0e6 and:[ self > 1.0e-4 ]) ifTrue:[
-        self absDecimalPrintOn:aStream digits:digits
+	self absDecimalPrintOn:aStream digits:digits
     ] ifFalse:[
-        self absScientificPrintOn:aStream digits:digits
+	self absScientificPrintOn:aStream digits:digits
     ]
 ! !
 
 !Float methodsFor:'private'!
 
-absScientificPrintOn:aStream digits:digits 
+absScientificPrintOn:aStream digits:digits
     "Place a string representation of the receiver's abs value on <aStream> using <digits> significant
      digits, using scientific notation.
      This is a helper for printf."
-    
+
     |exp fuzz x q i|
 
     "x is myself normalized to [1.0, 10.0), exp is my exponent"
-    exp := self abs < 1.0 
-            ifTrue:[ (10.0 / self abs) log floor negated ] 
-            ifFalse:[ self abs log floor ].
+    exp := self abs < 1.0
+	    ifTrue:[ (10.0 / self abs) log floor negated ]
+	    ifFalse:[ self abs log floor ].
     x := self abs / (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 "check if rounding has unnormalized x" ifTrue:[
-        x := x / 10.0.
-        exp := exp + 1
+	x := x / 10.0.
+	exp := exp + 1
     ].
     q := exp.
     exp := 0.
     [ x >= fuzz ] "use fuzz to track significance" whileTrue:[
-        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:$.
-        ]
+	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:$0.
+	exp := exp - 1.
+	exp = -1 ifTrue:[
+	    aStream nextPut:$.
+	]
     ].
     aStream nextPut:$e.
     q printOn:aStream
@@ -749,10 +749,10 @@
     "/ for now, use an interestConverter, which is somewhat less efficient.
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
-    self addInterest:(InterestConverter 
-                            destination:anObject 
-                            selector:aSelector 
-                            aspect:aspect)
+    self addInterest:(InterestConverter
+			    destination:anObject
+			    selector:aSelector
+			    aspect:aspect)
 
     "
      |p b|
@@ -839,11 +839,11 @@
     coll := IdentitySet new.
 
     deps do:[:dep |
-        (dep isInterestConverter) ifTrue:[
-            dep destination == someOne ifTrue:[
-                coll add:dep.
-            ]
-        ]
+	(dep isInterestConverter) ifTrue:[
+	    dep destination == someOne ifTrue:[
+		coll add:dep.
+	    ]
+	]
     ].
     ^ coll
 
@@ -860,9 +860,9 @@
 
     na := aBlock numArgs.
     na == 0 ifTrue:[
-        selector := #value
+	selector := #value
     ] ifFalse:[
-        selector := #( #'value:' #'value:value:' #'value:value:value:') at:na
+	selector := #( #'value:' #'value:value:' #'value:value:value:') at:na
     ].
     ^ self onChangeSend:selector to:aBlock
 
@@ -893,16 +893,16 @@
     "/ In the future, a more intelligent DependencyCollection class is planned for
 
     ((self interests ? #())
-        contains:[:anInterest |
-            (anInterest isInterestConverter)
-            and:[ anInterest destination == anObject
-            and:[ anInterest selector == aSelector]]
-        ])
-            ifTrue:[^ self].
+	contains:[:anInterest |
+	    (anInterest isInterestConverter)
+	    and:[ anInterest destination == anObject
+	    and:[ anInterest selector == aSelector]]
+	])
+	    ifTrue:[^ self].
 
-    self addInterest:(InterestConverter 
-                          destination:anObject 
-                          selector:aSelector)
+    self addInterest:(InterestConverter
+			  destination:anObject
+			  selector:aSelector)
 
     "
      |p b|
@@ -1036,7 +1036,7 @@
 !Object methodsFor:'dependents-interests'!
 
 retractInterestsFor:someOne
-    "remove the interest of someOne in the receiver 
+    "remove the interest of someOne in the receiver
      (as installed with #onChangeSend:to:)."
 
     "/ for now, remove the interestConverter.
@@ -1094,16 +1094,16 @@
 
     deps := self interests.
     deps size ~~ 0 ifTrue:[
-        "/ cannot removeDependent within the loop - the interests collection rehashes
-        coll := OrderedCollection new.
-        deps do:[:dep |
-            dep isInterestConverter ifTrue:[
-                (aBlock value:dep) ifTrue:[coll add:dep].
-            ]
-        ].
-        coll do:[:dep |
-            self removeInterest:dep.
-        ].
+	"/ cannot removeDependent within the loop - the interests collection rehashes
+	coll := OrderedCollection new.
+	deps do:[:dep |
+	    dep isInterestConverter ifTrue:[
+		(aBlock value:dep) ifTrue:[coll add:dep].
+	    ]
+	].
+	coll do:[:dep |
+	    self removeInterest:dep.
+	].
     ].
 ! !
 
@@ -1126,9 +1126,9 @@
      Here, we use the nonWeakDependencies."
 
     self addInterest:(InterestConverterWithParameters
-                            destination:anObject 
-                            selector:selector 
-                            aspect:eventSymbol).
+			    destination:anObject
+			    selector:selector
+			    aspect:eventSymbol).
 
     "
      |p b|
@@ -1143,3 +1143,12 @@
     "
 ! !
 
+!stx_libbasic2 class methodsFor:'documentation'!
+
+extensionsVersion_CVS
+    ^ '$Header: /cvs/stx/stx/libbasic2/extensions.st,v 1.15 2009-10-09 16:27:07 cg Exp $'
+!
+
+extensionsVersion_SVN
+    ^ 'Id:'
+! !