CharacterArray.st
changeset 13362 ee643208df42
parent 13344 ec6860c49990
child 13504 66059f9c83cd
equal deleted inserted replaced
13361:e9e42eb53f34 13362:ee643208df42
  1505 isCharacters
  1505 isCharacters
  1506     "added for visual works compatibility"
  1506     "added for visual works compatibility"
  1507     ^ true
  1507     ^ true
  1508 ! !
  1508 ! !
  1509 
  1509 
  1510 !CharacterArray methodsFor:'binary storage'!
       
  1511 
       
  1512 storeBinaryDefinitionOn:stream manager:manager
       
  1513     "append a binary representation of the receiver onto stream.
       
  1514      This is an internal interface for the binary storage mechanism."
       
  1515 
       
  1516     |myClass|
       
  1517 
       
  1518     "not, if I have named instance variables"
       
  1519     (myClass := self class) instSize ~~ 0 ifTrue:[
       
  1520         ^ super storeBinaryDefinitionOn:stream manager:manager
       
  1521     ].
       
  1522 
       
  1523     manager putIdOfClass:myClass on:stream.
       
  1524     stream nextNumber:4 put:self basicSize.
       
  1525     self storeBinaryElementsOn:stream.
       
  1526 !
       
  1527 
       
  1528 storeBinaryElementsOn:aStream
       
  1529     aStream nextPutBytes:self basicSize from:self startingAt:1.
       
  1530 ! !
       
  1531 
  1510 
  1532 !CharacterArray methodsFor:'character searching'!
  1511 !CharacterArray methodsFor:'character searching'!
  1533 
  1512 
  1534 includesMatchCharacters
  1513 includesMatchCharacters
  1535     "return true if the receiver includes any GLOB meta-match characters (i.e. $* or $#)
  1514     "return true if the receiver includes any GLOB meta-match characters (i.e. $* or $#)
  2675      'HelloWorld' asLowercase
  2654      'HelloWorld' asLowercase
  2676      'HelloWorlD' asLowercaseLast
  2655      'HelloWorlD' asLowercaseLast
  2677     "
  2656     "
  2678 !
  2657 !
  2679 
  2658 
  2680 asMimeType
       
  2681     ^ MIMETypes mimeTypeFromString:self string
       
  2682 
       
  2683     "
       
  2684      'text/html' asMimeType isTextType
       
  2685      'text/html' asMimeType isImage
       
  2686      'image/gif' asMimeType isImage
       
  2687     "
       
  2688 !
       
  2689 
       
  2690 asNumber
  2659 asNumber
  2691     "read a number from the receiver.
  2660     "read a number from the receiver.
  2692      Notice, that (in contrast to ST-80) errors may occur during the read,
  2661      Notice, that (in contrast to ST-80) errors may occur during the read,
  2693      so you better setup some signal handler when using this method.
  2662      so you better setup some signal handler when using this method.
  2694      Also notice, that this is meant to read end-user numbers from a string;
  2663      Also notice, that this is meant to read end-user numbers from a string;
  3052 
  3021 
  3053     "Modified: 1.9.1995 / 02:25:45 / claus"
  3022     "Modified: 1.9.1995 / 02:25:45 / claus"
  3054     "Modified: 22.4.1996 / 13:00:50 / cg"
  3023     "Modified: 22.4.1996 / 13:00:50 / cg"
  3055 !
  3024 !
  3056 
  3025 
  3057 scanf:dataStream
       
  3058     "Return a Collection of objects found in the Character Stream
       
  3059      <dataStream> as interpreted according to the receiver.
       
  3060      The receiver is assumed to be a conversion control string as
       
  3061      specified in the Unix C-language manual page for scanf(3).
       
  3062      For copyright information, see goodies/String-printf_scanf.chg"
       
  3063 
       
  3064     |results format char|
       
  3065 
       
  3066     results := OrderedCollection new.
       
  3067     format := ReadStream on:self.
       
  3068     [ format atEnd ] whileFalse:[
       
  3069 	char := format next.
       
  3070 	(char == Character space or:[ char == Character tab ]) ifTrue:[
       
  3071 	    dataStream skipSeparators.
       
  3072 	    format skipSeparators
       
  3073 	].
       
  3074 	char == $% ifTrue:[
       
  3075 	    self
       
  3076 		scanf_scanArgFrom:dataStream
       
  3077 		to:results
       
  3078 		format:format
       
  3079 	] ifFalse:[
       
  3080 	    dataStream peekFor:char
       
  3081 	]
       
  3082     ].
       
  3083     ^ results
       
  3084 
       
  3085     "
       
  3086      '%d %x' scanf:(ReadStream on:'1234 ff00')
       
  3087     "
       
  3088 !
       
  3089 
       
  3090 sscanf:string
       
  3091     "Return a Collection of objects found in <string> as
       
  3092      interpreted according to the receiver.
       
  3093      The receiver is assumed to be a conversion control string as
       
  3094      specified in the Unix C-language manual page for scanf(3).
       
  3095      For copyright information, see goodies/String-printf_scanf.chg"
       
  3096 
       
  3097     ^ self scanf:(ReadStream on:string)
       
  3098 
       
  3099     "
       
  3100      '%d %x' sscanf:'1234 ff00'
       
  3101      '%d %x %b' sscanf:'1234 ff00 1001'
       
  3102     "
       
  3103 !
       
  3104 
       
  3105 string
  3026 string
  3106     "return the receiver - for ST-80 compatibility"
  3027     "return the receiver - for ST-80 compatibility"
  3107 
  3028 
  3108     ^ self
  3029     ^ self
  3109 
  3030 
  3325     "if the receivers size is less or equal to maxLen, return it.
  3246     "if the receivers size is less or equal to maxLen, return it.
  3326      Otherwise, return a copy of the receiver, where some characters
  3247      Otherwise, return a copy of the receiver, where some characters
  3327      in the middle have been replaced by '...' for a total string length
  3248      in the middle have been replaced by '...' for a total string length
  3328      of maxLen. Can be used to abbreviate long entries in tables."
  3249      of maxLen. Can be used to abbreviate long entries in tables."
  3329 
  3250 
  3330     |sz "{ SmallInteger }"
  3251     |sz "{ SmallInteger }" leftSize rightSize|
  3331      halfSize "{ SmallInteger }"
       
  3332      leftEnd rightStart|
       
  3333 
  3252 
  3334     (sz := self size) <= maxLen ifTrue:[ ^ self ].
  3253     (sz := self size) <= maxLen ifTrue:[ ^ self ].
  3335 
  3254 
  3336     halfSize := maxLen // 2.
  3255     rightSize := maxLen // 2.
  3337     leftEnd := halfSize-1.
  3256     leftSize := maxLen - rightSize.
  3338     rightStart := sz-halfSize+2.
  3257     leftSize := leftSize - 1.
  3339     halfSize even ifTrue:[
  3258     rightSize := rightSize - 2.
  3340 	rightStart := rightStart+1.
  3259     ^ (self copyTo:leftSize),'...',(self copyFrom:(sz+1-rightSize))
  3341     ].
  3260 
  3342     ^ (self copyTo:leftEnd),'...',(self copyFrom:rightStart)
  3261     "
  3343 
  3262      '12345678901234' contractTo:15          
  3344     "
       
  3345      '12345678901234' contractTo:15
       
  3346      '123456789012345' contractTo:15
  3263      '123456789012345' contractTo:15
  3347      '1234567890123456' contractTo:15
  3264      '1234567890123456' contractTo:15 
  3348      'aShortString' contractTo:15
  3265      'aShortString' contractTo:15  
  3349      'aVeryLongNameForAStringThatShouldBeShortened' contractTo:15
  3266      'aVeryLongNameForAStringThatShouldBeShortened' contractTo:15
  3350      'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractTo:40
  3267      'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractTo:40
  3351     "
  3268      ('1234567890123456789012345678901234567' contractTo:30) size  
  3352 
  3269      ('1234567890123456789012345678901234567' contractTo:29) size   
  3353     "Modified: / 24-10-2006 / 12:23:56 / cg"
  3270     "
       
  3271 
       
  3272     "Modified: / 05-05-2011 / 16:28:15 / cg"
  3354 !
  3273 !
  3355 
  3274 
  3356 copyReplaceString:subString withString:newString
  3275 copyReplaceString:subString withString:newString
  3357     "return a copy of the receiver, with all sequences of subString replaced
  3276     "return a copy of the receiver, with all sequences of subString replaced
  3358      by newString (i.e. slice in the newString in place of the oldString)."
  3277      by newString (i.e. slice in the newString in place of the oldString)."
  3794     "
  3713     "
  3795 
  3714 
  3796     "Modified: / 11-05-2010 / 19:12:37 / cg"
  3715     "Modified: / 11-05-2010 / 19:12:37 / cg"
  3797 ! !
  3716 ! !
  3798 
  3717 
  3799 !CharacterArray methodsFor:'inspecting'!
       
  3800 
       
  3801 inspectorExtraAttributes
       
  3802     "extra (pseudo instvar) entries to be shown in an inspector."
       
  3803 
       
  3804     |d|
       
  3805 
       
  3806     d := Dictionary new
       
  3807 	declareAllNewFrom:(super inspectorExtraAttributes ? #());
       
  3808 	add:'-utf8String' -> [ self utf8Encoded ];
       
  3809 	add:'-utf8' -> [ self utf8Encoded asByteArray hexPrintStringWithSeparator:Character space ];
       
  3810 	yourself.
       
  3811 
       
  3812     HTMLUtilities notNil ifTrue:[
       
  3813 	d add:'-html' -> [ HTMLUtilities escapeCharacterEntities:self ].
       
  3814     ].
       
  3815     ^ d
       
  3816 
       
  3817     "
       
  3818      'aouäöü' inspect
       
  3819     "
       
  3820 
       
  3821     "Created: / 22-10-2006 / 03:52:20 / cg"
       
  3822 ! !
       
  3823 
  3718 
  3824 !CharacterArray methodsFor:'matching - glob expressions'!
  3719 !CharacterArray methodsFor:'matching - glob expressions'!
  3825 
  3720 
  3826 compoundMatch:aString
  3721 compoundMatch:aString
  3827     "like match, but the receiver may be a compound match pattern,
  3722     "like match, but the receiver may be a compound match pattern,
  4245      NOTICE: the receiver is the match pattern"
  4140      NOTICE: the receiver is the match pattern"
  4246 
  4141 
  4247     ^ aPatternString match:self
  4142     ^ aPatternString match:self
  4248 ! !
  4143 ! !
  4249 
  4144 
  4250 !CharacterArray methodsFor:'matching - phonetic'!
       
  4251 
       
  4252 asKoelnerPhoneticCode
       
  4253     "return a koelner phonetic code.
       
  4254      The koelnerPhonetic code is for the german language what the soundex code is for english;
       
  4255      it returns simular strings for similar sounding words.
       
  4256      There are some differences to soundex, though:
       
  4257 	its length is not limited to 4, but depends on the length of the original string;
       
  4258 	it does not start with the first character of the input.
       
  4259 
       
  4260      Caveat: this phonetic code is especially suited for german words.
       
  4261 	     Please have a look at the other phonetic comparison operators found
       
  4262 	     in PhoneticStringUtilities."
       
  4263 
       
  4264     ^ PhoneticStringUtilities koelnerPhoneticCodeOf:self
       
  4265 
       
  4266     "
       
  4267      #(
       
  4268 	'Müller'
       
  4269 	'Miller'
       
  4270 	'Mueller'
       
  4271 	'Mühler'
       
  4272 	'Mühlherr'
       
  4273 	'Mülherr'
       
  4274 	'Myler'
       
  4275 	'Millar'
       
  4276 	'Myller'
       
  4277 	'Müllar'
       
  4278 	'Müler'
       
  4279 	'Muehler'
       
  4280 	'Mülller'
       
  4281 	'Müllerr'
       
  4282 	'Muehlherr'
       
  4283 	'Muellar'
       
  4284 	'Mueler'
       
  4285 	'Mülleer'
       
  4286 	'Mueller'
       
  4287 	'Nüller'
       
  4288 	'Nyller'
       
  4289 	'Niler'
       
  4290 	'Czerny'
       
  4291 	'Tscherny'
       
  4292 	'Czernie'
       
  4293 	'Tschernie'
       
  4294 	'Schernie'
       
  4295 	'Scherny'
       
  4296 	'Scherno'
       
  4297 	'Czerne'
       
  4298 	'Zerny'
       
  4299 	'Tzernie'
       
  4300 	'Breschnew'
       
  4301      ) do:[:w |
       
  4302 	 Transcript show:w; show:'->'; showCR:(w asKoelnerPhoneticCode)
       
  4303      ].
       
  4304     "
       
  4305 
       
  4306     "
       
  4307      'Breschnew' asKoelnerPhoneticCode -> '17863'
       
  4308      'Breschnew' asKoelnerPhoneticCode -> '17863'
       
  4309      'Breschneff' asKoelnerPhoneticCode -> '17863'
       
  4310      'Braeschneff' asKoelnerPhoneticCode -> '17863'
       
  4311      'Braessneff' asKoelnerPhoneticCode -> '17863'
       
  4312      'Pressneff' asKoelnerPhoneticCode -> '17863'
       
  4313      'Presznäph' asKoelnerPhoneticCode -> '17863'
       
  4314     "
       
  4315 !
       
  4316 
       
  4317 asSoundexCode
       
  4318     "return a soundex phonetic code or nil.
       
  4319      Soundex returns similar codes for similar sounding words, making it a useful
       
  4320      tool when searching for words where the correct spelling is unknown.
       
  4321      (read Knuth or search the web if you dont know what a soundex code is).
       
  4322 
       
  4323      Caveat: 'similar sounding words' means: 'similar sounding in ENGLISH'
       
  4324 	     Please have a look at the other phonetic comparison operators found
       
  4325 	     in PhoneticStringUtilities."
       
  4326 
       
  4327     ^ PhoneticStringUtilities soundexCodeOf:self
       
  4328 
       
  4329     "
       
  4330      'claus' asSoundexCode
       
  4331      'clause' asSoundexCode
       
  4332      'close' asSoundexCode
       
  4333      'smalltalk' asSoundexCode
       
  4334      'smaltalk' asSoundexCode
       
  4335      'smaltak' asSoundexCode
       
  4336      'smaltok' asSoundexCode
       
  4337      'smoltok' asSoundexCode
       
  4338      'aa' asSoundexCode
       
  4339      'by' asSoundexCode
       
  4340      'bab' asSoundexCode
       
  4341      'bob' asSoundexCode
       
  4342      'bop' asSoundexCode
       
  4343     "
       
  4344 ! !
       
  4345 
  4145 
  4346 !CharacterArray methodsFor:'matching - regex'!
  4146 !CharacterArray methodsFor:'matching - regex'!
  4347 
  4147 
  4348 hasAnyRegexMatches: rxString
  4148 hasAnyRegexMatches: rxString
  4349     "return true, if any substrings in the receiver, matches the regular expression in rxString"
  4149     "return true, if any substrings in the receiver, matches the regular expression in rxString"
  4656 
  4456 
  4657     "Modified: / 15.6.1998 / 17:21:17 / cg"
  4457     "Modified: / 15.6.1998 / 17:21:17 / cg"
  4658     "Created: / 15.6.1998 / 17:22:13 / cg"
  4458     "Created: / 15.6.1998 / 17:22:13 / cg"
  4659 !
  4459 !
  4660 
  4460 
  4661 printf:args
       
  4662     "Format and print the receiver with <args> formatted in C style,
       
  4663      as specified in the Unix C-language manual page for printf(3).
       
  4664      Return the resulting string.
       
  4665 
       
  4666      For copyright information, see goodies/String-printf_scanf.chg"
       
  4667 
       
  4668     |aStream|
       
  4669 
       
  4670     aStream := WriteStream on:String new.
       
  4671     self printf:args on:aStream.
       
  4672     ^ aStream contents
       
  4673 
       
  4674     "
       
  4675      Transcript showCR:('%05x %d %f %o' printf:{ 123. 234*5. 1.234. 8r377 } )
       
  4676     "
       
  4677 
       
  4678     "
       
  4679      Transcript showCR: 'Some examples:'!!
       
  4680 
       
  4681      Transcript show:'''%#x %#X %03o%*.*s'' printf: #(16rABCD 16rEF 5 9 5 ''ghijklmn'') = .'.
       
  4682      Transcript show: ('%#x %#X %03o%*.*s' printf: #(16rABCD 16rEF 5 9 5 'ghijklmn')).
       
  4683      Transcript showCR: '.'
       
  4684 
       
  4685      Transcript show: '''%- 10.4s%.2e'' printf: (Array with: ''abcdefghijkl'' with: Float pi) = .'.
       
  4686      Transcript show: ('%- 10.4s%.2e' printf: (Array with: 'abcdefghijkl' with: Float pi)).
       
  4687      Transcript showCR: '.'
       
  4688 
       
  4689      Transcript show: '''%8.3f'' printf: (Array with: 200 sqrt negated) = .'.
       
  4690      Transcript show: ('%8.3f' printf: (Array with: 200 sqrt negated)).
       
  4691      Transcript showCR: '.'
       
  4692 
       
  4693      Transcript show: '''%c'' printf: #(16r41) = .'.
       
  4694      Transcript show: ('%c' printf: #(16r41)).
       
  4695      Transcript showCR: '.'
       
  4696 
       
  4697      Transcript show: '''%f%2s%s%s%s'' sscanf: ''237.0 this is a test'' = '.
       
  4698      Transcript showCR: ('%f%2s%s%s%s'  sscanf: '237.0 this is a test') printString.
       
  4699 
       
  4700      Transcript show: '''%d%f%s'' sscanf: ''25 54.32e-01 monday'' = '.
       
  4701      Transcript showCR: ('%d%f%s' sscanf: '25 54.32e-01 monday') printString.
       
  4702 
       
  4703      Transcript show: '''%f%*f %8[A-F0-9]%c%d 0x%x%f'' sscanf: ''12.45 1048.73 AE40Z527 0x75BCD15 34'' = '.
       
  4704      Transcript showCR: ('%f%*f %8[A-F0-9]%c%d 0x%x%f' sscanf: '12.45 1048.73 AE40Z527 0x75BCD15 34') printString.
       
  4705     "
       
  4706 !
       
  4707 
       
  4708 printf:args on:outStream
       
  4709     "Format and print the receiver on <outStream> with <args>
       
  4710      formatted in C style, as specified in the Unix C-language manual page for printf(3).
       
  4711 
       
  4712      For copyright information, see goodies/String-printf_scanf.chg"
       
  4713 
       
  4714     |argStream inStream char|
       
  4715 
       
  4716     argStream := ReadStream on:args.
       
  4717     inStream := ReadStream on:self.
       
  4718     [ inStream atEnd ] whileFalse:[
       
  4719 	(char := inStream next) == $% ifFalse:[
       
  4720 	    outStream nextPut:char
       
  4721 	] ifTrue:[
       
  4722 	    self
       
  4723 		printf_printArgFrom:inStream
       
  4724 		to:outStream
       
  4725 		withData:argStream
       
  4726 	]
       
  4727     ]
       
  4728 !
       
  4729 
       
  4730 printfWith:arg1
       
  4731     "Format and print the receiver with <arg1> formatted in C style,
       
  4732      as specified in the Unix C-language manual page for printf(3).
       
  4733      Return the resulting string."
       
  4734 
       
  4735     ^ self printf:(Array with:arg1)
       
  4736 
       
  4737     "
       
  4738      Transcript showCR:('%05x' printfWith:123)
       
  4739     "
       
  4740 !
       
  4741 
       
  4742 printfWith:arg1 with:arg2
       
  4743     "Format and print the receiver with <argI> formatted in C style,
       
  4744      as specified in the Unix C-language manual page for printf(3).
       
  4745      Return the resulting string."
       
  4746 
       
  4747     ^ self printf:(Array with:arg1 with:arg2)
       
  4748 
       
  4749     "
       
  4750      Transcript showCR:('%d %05x' printfWith:123 with:234)
       
  4751     "
       
  4752 !
       
  4753 
       
  4754 printfWith:arg1 with:arg2 with:arg3
       
  4755     "Format and print the receiver with <argI> formatted in C style,
       
  4756      as specified in the Unix C-language manual page for printf(3).
       
  4757      Return the resulting string."
       
  4758 
       
  4759     ^ self printf:(Array with:arg1 with:arg2 with:arg3)
       
  4760 
       
  4761     "
       
  4762      Transcript showCR:('%d %05x %08o' printfWith:123 with:234 with:345)
       
  4763     "
       
  4764 !
       
  4765 
       
  4766 printfWith:arg1 with:arg2 with:arg3 with:arg4
       
  4767     "Format and print the receiver with <argI> formatted in C style,
       
  4768      as specified in the Unix C-language manual page for printf(3).
       
  4769      Return the resulting string."
       
  4770 
       
  4771     ^ self printf:(Array with:arg1 with:arg2 with:arg3 with:arg4)
       
  4772 
       
  4773     "
       
  4774      Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)
       
  4775     "
       
  4776 !
       
  4777 
       
  4778 printfWith:arg1 with:arg2 with:arg3 with:arg4 with:arg5
  4461 printfWith:arg1 with:arg2 with:arg3 with:arg4 with:arg5
  4779     "Format and print the receiver with <argI> formatted in C style,
  4462     "Format and print the receiver with <argI> formatted in C style,
  4780      as specified in the Unix C-language manual page for printf(3).
  4463      as specified in the Unix C-language manual page for printf(3).
  4781      Return the resulting string."
  4464      Return the resulting string."
  4782 
  4465 
  4783     ^ self printf:(Array with:arg1 with:arg2 with:arg3 with:arg4 with:arg5)
  4466     ^ self printf:(Array with:arg1 with:arg2 with:arg3 with:arg4 with:arg5)
  4784 
  4467 
  4785     "
  4468     "
  4786      Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)
  4469      Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)
  4787     "
  4470     "
  4788 !
       
  4789 
       
  4790 printf_formatArgCount
       
  4791     "Return the number of arguments required/produced if the receiver is interpreted
       
  4792      as a printf/scanf format control string.
       
  4793      For copyright information, see goodies/String-printf_scanf.chg"
       
  4794 
       
  4795     |nonConsecutive count|
       
  4796 
       
  4797     nonConsecutive := true.
       
  4798     count := 0.
       
  4799     self do:[:c |
       
  4800 	c == $% ifTrue:[
       
  4801 	    nonConsecutive ifTrue:[
       
  4802 		count := count + 1.
       
  4803 		nonConsecutive := false
       
  4804 	    ] ifFalse:[
       
  4805 		count := count - 1.
       
  4806 		nonConsecutive := true
       
  4807 	    ]
       
  4808 	] ifFalse:[
       
  4809 	    nonConsecutive := true
       
  4810 	]
       
  4811     ].
       
  4812     ^ count
       
  4813 !
       
  4814 
       
  4815 printf_printOn:outStream withData:args
       
  4816     <resource: #obsolete>
       
  4817 
       
  4818     "Format and print the receiver on <outStream> with <args>
       
  4819      formatted in C style, as specified in the Unix C-language manual page for printf(3).
       
  4820 
       
  4821      For copyright information, see goodies/String-printf_scanf.chg"
       
  4822 
       
  4823     self obsoleteMethodWarning:'use printf:on:'.
       
  4824     self printf:args on:outStream
       
  4825 ! !
  4471 ! !
  4826 
  4472 
  4827 !CharacterArray methodsFor:'private'!
       
  4828 
       
  4829 printf_printArgFrom:inStream to:outStream withData:argStream
       
  4830     "Interpret the required number of arguments from <argStream>
       
  4831      according to the formatting information in <inStream>.
       
  4832      Place the interpretation on <outStream>.
       
  4833      The interpretation is C printf(3) style, as
       
  4834      specified in the Unix C-language manual page for printf(3).
       
  4835      <inStream> is assumed to be positioned just past
       
  4836      $%, and a complete control string is assumed available.
       
  4837 
       
  4838      Return when the conversion control string is consumed.
       
  4839      Leave <inStream> pointing past the last character in the conversion control string.
       
  4840 
       
  4841      This code assumes that <inStream> is formatted according to
       
  4842      specification, and error checking is minimal.  Unexpected
       
  4843      results will be obtained by illegal control strings, or when
       
  4844      argument types do not match conversion codes, but it probably
       
  4845      won't dump core, like C does in such cases!!
       
  4846 
       
  4847      For copyright information, see goodies/String-printf_scanf.chg"
       
  4848 
       
  4849     |nextArg ljust plus pound width precision pad char arg argString|
       
  4850 
       
  4851     nextArg := [
       
  4852 		    argStream atEnd ifTrue:[
       
  4853 			self error:'not enough arguments for format string'
       
  4854 		    ].
       
  4855 		    argStream next
       
  4856 	       ].
       
  4857 
       
  4858     ljust := plus := pound := false.
       
  4859     width := 0.
       
  4860     precision := SmallInteger maxVal.
       
  4861     pad := $ .
       
  4862     char := inStream peek.
       
  4863     char == $% ifTrue:[
       
  4864 	^ outStream nextPut:inStream next
       
  4865     ].
       
  4866     char == $- ifTrue:[
       
  4867 	ljust := true.
       
  4868 	inStream next.
       
  4869 	char := inStream peek
       
  4870     ].
       
  4871     char == $  ifTrue:[
       
  4872 	outStream space.
       
  4873 	inStream next.
       
  4874 	char := inStream peek
       
  4875     ].
       
  4876     char == $+ ifTrue:[
       
  4877 	plus := true.
       
  4878 	inStream next.
       
  4879 	char := inStream peek
       
  4880     ].
       
  4881     char == $# ifTrue:[
       
  4882 	pound := true.
       
  4883 	inStream next.
       
  4884 	char := inStream peek
       
  4885     ].
       
  4886     char == $* ifTrue:[
       
  4887 	width := nextArg value.
       
  4888 	inStream next.
       
  4889 	char := inStream peek
       
  4890     ].
       
  4891     char isDigit ifTrue:[
       
  4892 	char == $0 ifTrue:[
       
  4893 	    pad := $0
       
  4894 	].
       
  4895 	width := Integer readFrom:inStream.
       
  4896 	char := inStream peek
       
  4897     ].
       
  4898     char == $. ifTrue:[
       
  4899 	inStream next.
       
  4900 	char := inStream peek.
       
  4901 	char == $* ifTrue:[
       
  4902 	    precision := nextArg value.
       
  4903 	    inStream next.
       
  4904 	    char := inStream peek
       
  4905 	] ifFalse:[
       
  4906 	    precision := Integer readFrom:inStream.
       
  4907 	    char := inStream peek
       
  4908 	]
       
  4909     ].
       
  4910     char == $l "Ignore long specifier." ifTrue:[
       
  4911 	inStream next.
       
  4912 	char := inStream peek
       
  4913     ].
       
  4914     ('feg' includes:char) ifTrue:[
       
  4915 	arg := nextArg value asFloat.
       
  4916 	precision := precision min:6.
       
  4917 	argString := WriteStream on:String new.
       
  4918 	char == $g ifTrue:[
       
  4919 	    arg absPrintOn:argString digits:precision + 1
       
  4920 	].
       
  4921 	char == $f ifTrue:[
       
  4922 	    arg absDecimalPrintOn:argString digits:precision + arg abs log + 1
       
  4923 	].
       
  4924 	char == $e ifTrue:[
       
  4925 	    arg absScientificPrintOn:argString digits:precision + 1
       
  4926 	].
       
  4927 	argString := argString contents.
       
  4928 	arg < 0 ifTrue:[
       
  4929 	    argString := '-' , argString
       
  4930 	] ifFalse:[
       
  4931 	    plus ifTrue:[
       
  4932 		argString := '+' , argString
       
  4933 	    ]
       
  4934 	].
       
  4935 	(precision = 0 and:[ pound not ]) ifTrue:[
       
  4936 	    (argString includes:$e) ifTrue:[
       
  4937 		"self halt"
       
  4938 	    ] ifFalse:[
       
  4939 		argString := arg truncated printString
       
  4940 	    ]
       
  4941 	].
       
  4942 	pound ifTrue:[
       
  4943 	    (argString includes:$e) ifTrue:[
       
  4944 		"self halt"
       
  4945 	    ] ifFalse:[
       
  4946 		precision - (argString size - (argString indexOf:$.)) timesRepeat:[
       
  4947 		    argString := argString , '0'
       
  4948 		]
       
  4949 	    ]
       
  4950 	].
       
  4951 	ljust ifTrue:[
       
  4952 	    outStream nextPutAll:argString
       
  4953 	].
       
  4954 	width - argString size timesRepeat:[
       
  4955 	    outStream space
       
  4956 	].
       
  4957 	ljust ifFalse:[
       
  4958 	    outStream nextPutAll:argString
       
  4959 	].
       
  4960 	^ inStream next
       
  4961     ].
       
  4962     char == $c ifTrue:[
       
  4963 	arg := String with:nextArg value asCharacter
       
  4964     ].
       
  4965     char == $s "Assume the arg is a String or Symbol." ifTrue:[
       
  4966 	arg := nextArg value asString
       
  4967     ].
       
  4968     char == $d ifTrue:[
       
  4969 	arg := nextArg value asInteger printString.
       
  4970 	plus ifTrue:[
       
  4971 	    arg := '+' , arg
       
  4972 	]
       
  4973     ].
       
  4974     char == $u ifTrue:[
       
  4975 	arg := nextArg value asInteger abs printString
       
  4976     ].
       
  4977     char == $o ifTrue:[
       
  4978 	arg := nextArg value asInteger abs printStringRadix:8.
       
  4979 	pound ifTrue:[
       
  4980 	    arg := '0' , arg
       
  4981 	]
       
  4982     ].
       
  4983     char == $b ifTrue:[
       
  4984 	arg := nextArg value asInteger abs printStringRadix:2.
       
  4985 	pound ifTrue:[
       
  4986 	    arg := '0' , arg
       
  4987 	]
       
  4988     ].
       
  4989     ('xX' includes:char) ifTrue:[
       
  4990 	arg := nextArg value asInteger abs printStringRadix:16.
       
  4991 	pound ifTrue:[
       
  4992 	    arg := '0x' , arg
       
  4993 	]
       
  4994     ].
       
  4995     char == $x ifTrue:[
       
  4996 	1 to:arg size do:[:i |
       
  4997 	    ('ABCDEF' includes:(arg at:i)) ifTrue:[
       
  4998 		arg at:i put:((arg at:i) asciiValue + 16r20) asCharacter
       
  4999 	    ]
       
  5000 	]
       
  5001     ].
       
  5002     precision := precision min:arg size.
       
  5003     ljust ifTrue:[
       
  5004 	outStream nextPutAll:(arg copyFrom:1 to:precision)
       
  5005     ].
       
  5006     width - precision timesRepeat:[
       
  5007 	outStream nextPut:pad
       
  5008     ].
       
  5009     ljust ifFalse:[
       
  5010 	outStream nextPutAll:(arg copyFrom:1 to:precision)
       
  5011     ].
       
  5012     ^ inStream next
       
  5013 !
       
  5014 
       
  5015 scanf_scanArgFrom:dataStream to:collection format:format
       
  5016     "Add to <collection> an object who's representation is found
       
  5017      in <dataStream> interpreted according to the conversion
       
  5018      control string in the Stream <format>.
       
  5019      <format> is assumed to be positioned just past a $%, and a complete control
       
  5020      string is assumed available.
       
  5021 
       
  5022      Return when the conversion control string is consumed.  Leave
       
  5023      <format> pointing past the last character in the conversion
       
  5024      control string, leave <dataStream> pointing past any width
       
  5025      specified in <format>, or at the first character that doesn't
       
  5026      make sense for the <format>.
       
  5027 
       
  5028      For copyright information, see goodies/String-printf_scanf.chg"
       
  5029 
       
  5030     |final width char pos data scanset exclusive return last|
       
  5031 
       
  5032     final := [:retval |
       
  5033 	    collection add:retval.
       
  5034 	    data == dataStream ifFalse:[
       
  5035 		dataStream position:dataStream position + data position
       
  5036 	    ].
       
  5037 	    ^ self
       
  5038 	].
       
  5039     width := 0.
       
  5040     char := format peek.
       
  5041     char == $% ifTrue:[
       
  5042 	^ dataStream peekFor:char
       
  5043     ].
       
  5044     char == $* ifTrue:[
       
  5045 	format next.
       
  5046 	char := format peek.
       
  5047 	final := [:retval |
       
  5048 		data == dataStream ifFalse:[
       
  5049 		    dataStream position:dataStream position + data position
       
  5050 		].
       
  5051 		^ self
       
  5052 	    ]
       
  5053     ].
       
  5054     char isDigit ifTrue:[
       
  5055 	width := Integer readFrom:format.
       
  5056 	char := format peek
       
  5057     ].
       
  5058     ('slhduoxfeg' includes:char) ifTrue:[
       
  5059 	dataStream skipSeparators
       
  5060     ].
       
  5061     width = 0 ifTrue:[
       
  5062 	data := dataStream
       
  5063     ] ifFalse:[
       
  5064 	pos := dataStream position.
       
  5065 	data := ReadStream on:(dataStream next:width).
       
  5066 	dataStream position:pos
       
  5067     ].
       
  5068     char == $s ifTrue:[
       
  5069 	final value:(data upToSeparator)
       
  5070     ].
       
  5071     char == $c ifTrue:[
       
  5072 	width = 0 ifTrue:[
       
  5073 	    final value:(String with:data next)
       
  5074 	] ifFalse:[
       
  5075 	    final value:data contents
       
  5076 	]
       
  5077     ].
       
  5078     char == $[ "What a mess!!" ifTrue:[
       
  5079 	return := WriteStream on:(String new:8).
       
  5080 	scanset := IdentitySet new.
       
  5081 	format next.
       
  5082 	width = 0 ifTrue:[
       
  5083 	    width := SmallInteger maxVal
       
  5084 	].
       
  5085 	exclusive := format peekFor:$^.
       
  5086 	[
       
  5087 	    last := char.
       
  5088 	    char := format next.
       
  5089 	    char == $]
       
  5090 	] whileFalse:[
       
  5091 	    char == $- ifFalse:[
       
  5092 		scanset add:char
       
  5093 	    ] ifTrue:[
       
  5094 		(last to:format next) do:[:c |
       
  5095 		    scanset add:c
       
  5096 		]
       
  5097 	    ]
       
  5098 	].
       
  5099 	[
       
  5100 	    data atEnd not and:[ (scanset includes:data peek) xor:exclusive ]
       
  5101 	] whileTrue:[ return nextPut:data next ].
       
  5102 	final value:return contents
       
  5103     ].
       
  5104     ('lh' includes:char) ifTrue:[
       
  5105 	format next.
       
  5106 	char := format peek
       
  5107     ].
       
  5108     ('DUdu' includes:char) ifTrue:[
       
  5109 	final value:(Integer readFrom:data)
       
  5110     ].
       
  5111     ('FEGfeg' includes:char) ifTrue:[
       
  5112 	final value:(Float readFrom:data)
       
  5113     ].
       
  5114     ('b' includes:char) ifTrue:[
       
  5115 	final value:(Integer readFrom:data radix:2)
       
  5116     ].
       
  5117     ('Oo' includes:char) ifTrue:[
       
  5118 	final value:(Integer readFrom:data radix:8)
       
  5119     ].
       
  5120     ('Xx' includes:char) ifTrue:[
       
  5121 	final value:(Integer readFrom:data radix:16)
       
  5122     ]
       
  5123 
       
  5124     "
       
  5125      '%d %x' sscanf:'1234 ff00'
       
  5126      '%d %x %b' sscanf:'1234 ff00 1001'
       
  5127     "
       
  5128 ! !
       
  5129 
  4473 
  5130 !CharacterArray methodsFor:'queries'!
  4474 !CharacterArray methodsFor:'queries'!
  5131 
  4475 
  5132 bitsPerCharacter
  4476 bitsPerCharacter
  5133     "return the underlying strings bitsPerCharacter
  4477     "return the underlying strings bitsPerCharacter
  6567 ! !
  5911 ! !
  6568 
  5912 
  6569 !CharacterArray class methodsFor:'documentation'!
  5913 !CharacterArray class methodsFor:'documentation'!
  6570 
  5914 
  6571 version
  5915 version
  6572     ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.451 2011-04-20 08:34:07 stefan Exp $'
  5916     ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.452 2011-05-05 14:28:34 cg Exp $'
  6573 !
  5917 !
  6574 
  5918 
  6575 version_CVS
  5919 version_CVS
  6576     ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.451 2011-04-20 08:34:07 stefan Exp $'
  5920     ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.452 2011-05-05 14:28:34 cg Exp $'
  6577 ! !
  5921 ! !
  6578 
  5922 
  6579 CharacterArray initialize!
  5923 CharacterArray initialize!