CharacterArray.st
changeset 359 b8df66983eff
parent 357 82091a50055d
child 360 90c3608b92a3
--- a/CharacterArray.st	Tue Jun 06 06:01:20 1995 +0200
+++ b/CharacterArray.st	Tue Jun 27 04:15:21 1995 +0200
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1994 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.24 1995-06-06 03:53:15 claus Exp $
+$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.25 1995-06-27 02:11:58 claus Exp $
 '!
 
 !CharacterArray class methodsFor:'documentation'!
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.24 1995-06-06 03:53:15 claus Exp $
+$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.25 1995-06-27 02:11:58 claus Exp $
 "
 !
 
@@ -457,7 +457,8 @@
      in the middle have been replaced by '...' for a total string length
      of maxLen. Can be used to abbreviate long entries in tables."
 
-    |sz halfSize|
+    |sz "{ SmallInteger }"
+     halfSize "{ SmallInteger }"|
 
     (sz := self size) > maxLen ifTrue:[
 	halfSize := maxLen // 2.
@@ -617,7 +618,9 @@
     "return a copy of the receiver where leading spaces are
      replaced by tabulator characters (assuming 8-col tabs)"
 
-    |idx nTabs newString|
+    |idx   "{ SmallInteger }" 
+     nTabs "{ SmallInteger }" 
+     newString|
 
     idx := self findFirst:[:c | (c ~~ Character space)].
     nTabs := (idx-1) // 8.
@@ -643,7 +646,7 @@
     "return a copy of the receiver where all tabulator characters
      are expanded into spaces (assuming 8-col tabs)"
 
-    |idx str|
+    |idx "{ SmallInteger }" str|
 
     (self includes:(Character tab)) ifFalse:[^ self].
     str := WriteStream on:String new.
@@ -663,13 +666,135 @@
     ^ str contents
 !
 
+withEscapes
+    "return a new string consisting of receivers characters
+     with all \X-character escapes replaced by corresponding-characters.
+     (similar to the way C-language Strings are converted).
+     The following escapes are supported:
+	\r      return character
+	\n      newline character
+	\b      backspace character
+	\f      formfeed character
+	\t      tab character
+	\\      the \ character itself
+	\nnn    three digit octal number defining the characters ascii value
+	\other  other
+
+     Notice, that \' is NOT a valid escape, since the general syntax of
+     string constants is not affected by this method.
+
+     Although easily implementable, this is NOT done automatically
+     by the compiler (due to a lack of a language standard for this).
+     However, the compiler may detect sends ot #withEscapes to string literals
+     and place a modified string constant into the binary/byte-code.
+     Therefore, no runtime penalty will be payed for using these escapes.
+     (not in pre 2.11 versions)
+    "
+
+    |sz      "{ SmallInteger }"
+     newSize "{ SmallInteger }"
+     srcIdx  "{ SmallInteger }"
+     dstIdx  "{ SmallInteger }"
+     val     "{ SmallInteger }"
+     newString next start| 
+
+    "
+     first, count the number of escapes, to allow preallocation
+     of the new string ...
+     (it is faster to scan the string twice than to reallocate it multiple
+      times in a WriteStream)
+    "
+    sz := newSize := self size.
+    srcIdx := 1.
+    [(srcIdx := self indexOf:$\ startingAt:srcIdx) ~~ 0] whileTrue:[
+	srcIdx == sz ifFalse:[
+	    newSize := newSize - 1.
+	    srcIdx := srcIdx + 1.
+	    next := self at:srcIdx.
+	    next == $0 ifTrue:[
+		[(self at:srcIdx) isDigit] whileTrue:[
+		    newSize := newSize - 1. srcIdx := srcIdx + 1.
+		]
+	    ].
+	].
+	srcIdx := srcIdx + 1.
+    ].
+
+    newSize == sz ifTrue:[
+	^ self
+    ].
+
+    newString := self species new:newSize.
+    "
+     copy over, replace escapes
+    "
+    srcIdx := dstIdx := 1.
+    [srcIdx <= sz] whileTrue:[
+	next := self at:srcIdx.
+	srcIdx := srcIdx + 1.
+	next == $\ ifTrue:[
+	    srcIdx <= sz ifTrue:[
+		next := self at:srcIdx.
+		srcIdx := srcIdx + 1.
+		next == $r ifTrue:[
+		    next := Character return
+		] ifFalse:[
+		    next == $n ifTrue:[
+			next := Character nl
+		    ] ifFalse:[
+			next == $b ifTrue:[
+			    next := Character backspace
+			] ifFalse:[
+			    next == $f ifTrue:[
+				next := Character newPage
+			    ] ifFalse:[
+				next == $t ifTrue:[
+				    next := Character tab
+				] ifFalse:[
+				    next == $0 ifTrue:[
+					val := 0.
+					[next isDigit] whileTrue:[
+					    val := val * 8 + next digitValue.
+					    next := self at:srcIdx.
+					    srcIdx := srcIdx + 1.
+					].
+					next := Character value:val.
+				    ]
+				]
+			    ]
+			]
+		    ]
+		].
+	    ].
+	].
+	newString at:dstIdx put:next.
+	dstIdx := dstIdx + 1.
+    ].
+    ^ newString
+
+    "
+     'hello world' withEscapes  
+     'hello\world' withEscapes   
+     'hello\world\' withEscapes   
+     'hello world\' withEscapes   
+     'hello\tworld' withEscapes   
+     'hello\nworld\na\n\tnice\n\t\tstring' withEscapes   
+     'hello\tworld\n' withEscapes   
+     'hello\010world' withEscapes   
+     'hello\r\nworld' withEscapes   
+    "
+!
+
 expandPlaceholdersWith:argArray
     "return a copy of the receiver, where all %i escapes are
      replaced by corresponding arguments from the argArray.
      I.e. 'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') results
      in the new string 'hello world; how is this'."
 
-    |expandedString idx start stop next |
+    |expandedString next 
+     idx   "{ SmallInteger }"
+     start "{ SmallInteger }"
+     stop  "{ SmallInteger }"|
 
     expandedString := ''.
     stop := self size.
@@ -694,6 +819,7 @@
     "
      'hello %1' expandPlaceholdersWith:#('world') 
      'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') 
+     'hello %2; how is %1' expandPlaceholdersWith:#('world' 'this') 
     "
 ! !
 
@@ -1113,6 +1239,19 @@
 	startIndex := self indexOf:firstChar startingAt:(startIndex + 1)
     ].
     ^ exceptionBlock value
+!
+
+includesString:aString
+    "return true, if a substring is contained in the receiver"
+
+    ^ (self findString:aString) ~~ 0
+
+    "
+     'hello world' includesString:'hel' 
+     'hello world' includesString:'rld' 
+     'hello world' includesString:'llo'  
+     'hello world' includesString:'LLO'   
+    "
 ! !
 
 !CharacterArray class methodsFor:'pattern matching'!
@@ -1122,7 +1261,9 @@
      This is processed faster (especially with character ranges), and
      can also be reused later. (if the same pattern is to be searched again)"
 
-    |coll idx end c1 c2 matchSet previous|
+    |coll 
+     idx "{ Class: SmallInteger }"
+     end c1 c2 matchSet previous|
 
     coll := OrderedCollection new.
     idx := 1. end := aString size.
@@ -1491,6 +1632,20 @@
      '*ute*' match:'12345COMPUTER' from:1 to:5 ignoreCase:true 
      '*ute*' match:'12345COMPUTER' from:6 to:13 ignoreCase:true  
     "
+!
+
+includesMatchString:matchString
+    "like includesString, but allowing match patterns.
+     find matchstring; if found, return true, otherwise return false"
+
+    ^ (self findMatchString:matchString) ~~ 0
+
+    "
+     'hello world' includesMatchString:'h*'
+     'hello world' includesMatchString:'h[aeiou]llo' 
+     'hello world' includesMatchString:'wor*'     
+     'hello world' includesMatchString:'woR*'     
+    "
 ! !
 
 !CharacterArray methodsFor:'testing'!
@@ -1851,3 +2006,4 @@
 encoding
     ^ #unknown
 ! !
+