StringCollection.st
author Claus Gittinger <cg@exept.de>
Thu, 14 May 2009 12:06:39 +0200
changeset 11702 acba3579dbd7
parent 11596 82e1714ecb9a
child 13331 ef482782e3b4
child 17711 39faaaf888b4
permissions -rw-r--r--
+withoutXXXBlankLines

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

OrderedCollection subclass:#StringCollection
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text'
!

!StringCollection class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    StringCollection is an variable sized array of lines which are strings.
    WARNING:
        This class is temporary (a historic leftover) - it may change or
        even vanish in the future. Use OrderedCollections or other standard
        classes to represent collections of strings.

    StringCollection used to be called Text, but this is a very bad name
     - there is something totally different also named Text in ST-80 ...

    [author:]
        Claus Gittinger
"
! !

!StringCollection class methodsFor:'instance creation'!

from:aString
    <resource: #obsolete>
    "return a new text object with lines taken from the argument, aString"

    self obsoleteMethodWarning:'use #fromString:'.
    ^ self fromString:aString.
!

fromArray:anArray
    "return a new text object with lines taken from the argument, an array
     of strings"

    |newStringCollection
     size "{ Class: SmallInteger }" |

    size := anArray size.
    newStringCollection := self new:size.
    1 to:size do:[:line |
	newStringCollection at:line put:(anArray at:line)
    ].
    ^ newStringCollection
!

fromString:aString
    "return a new text object with lines taken from the argument, aString"

    ^ (self new:1) fromString:aString
!

new:size
    "return a new string collection with size empty lines"

    ^ (super new:size) grow:size
!

withSize:size
    "return a new string collection with size empty lines"

    ^ (super new:size) grow:size
! !

!StringCollection methodsFor:'converting'!

asString
    "return myself as a string with embedded cr's"

    ^ self 
        asStringWith:Character cr
        from:1 to:(self size) 
        compressTabs:false 
        final:Character cr
!

asStringCollection
    "return the receiver as a stringCollection - thats easy"

    ^ self
!

asStringWithoutEmphasis
    "return myself as a string with embedded cr's, but drop any emphasis"

    ^ self 
        asStringWith:Character cr
        from:1 to:(self size) 
        compressTabs:false 
        final:Character cr
        withEmphasis:false

    "Created: / 17.6.1998 / 12:32:48 / cg"
!

asStringWithoutFinalCR
    "return myself as a string with embedded cr's
     but do not add a final CR"

    ^ self 
        asStringWith:Character cr
        from:1 to:(self size) 
        compressTabs:false 
        final:nil
!

encodeFrom:oldEncoding into:newEncoding
    |enc|

    enc := CharacterEncoder encoderToEncodeFrom:oldEncoding into:newEncoding.
    ^ self collect:[:line |
        line isNil 
            ifTrue:[ nil ]
            ifFalse:[ enc encodeString:line]
      ]
!

from:aString
    <resource: #obsolete>
    "setup my contents from the argument, aString"

    self obsoleteMethodWarning:'use #fromString:'.
    ^ self fromString:aString
!

fromString:aString
    "setup my contents from the argument, aString"

    |numberOfLines "{ Class:SmallInteger }"
     start         "{ Class:SmallInteger }"
     stop          "{ Class:SmallInteger }" 
    |

    numberOfLines := aString occurrencesOf:(Character cr).
    (aString endsWith:(Character cr)) ifFalse:[
        numberOfLines := numberOfLines + 1.
    ].
    self grow:numberOfLines.

    start := 1.
    1 to:numberOfLines do:[:lineNr |
        stop := aString indexOf:(Character cr) startingAt:start.
        stop == 0 ifTrue:[
            self at:lineNr put:(aString copyFrom:start).
            self from:lineNr+1 to:numberOfLines put:''.
            ^ self.
        ].

        self at:lineNr put:(aString copyFrom:start to:stop-1).
        start := stop + 1
    ]

    "Modified: / 12.11.2001 / 18:18:42 / cg"
! !

!StringCollection methodsFor:'copying'!

copyEmpty:size
    "we have to redefine this, since 'self class new:size' does allocate size nil lines.
     In order to get collect working, we have to undo this allocation"

    ^ (super copyEmpty:size) grow:0.

    "Created: 14.2.1996 / 11:05:47 / stefan"
!

withoutLeadingBlankLines
    "return a copy of the receiver with leading blank lines removed.
     If there are no leading blank lines, the original receiver is returned.
     If all lines are blank, an empty string collection is returned."

    |indexOfFirstNonBlankLine|

    indexOfFirstNonBlankLine := self findFirst:[:line | line notEmptyOrNil and:[line isBlank not]].
    indexOfFirstNonBlankLine == 0 ifTrue:[ ^ self copyEmpty ].
    indexOfFirstNonBlankLine == 1 ifTrue:[ ^ self ].
    ^ self copyFrom:indexOfFirstNonBlankLine

    "
'1
2
3' asStringCollection withoutLeadingBlankLines     
    "

    "
'
2
3' asStringCollection withoutLeadingBlankLines       
    "

    "
'

' asStringCollection withoutLeadingBlankLines      
    "
!

withoutTrailingBlankLines
    "return a copy of the receiver with trailing blank lines removed.
     If there are no trailing blank lines, the original receiver is returned.
     If all lines are blank, an empty string collection is returned."

    |indexOfLastNonBlankLine|

    indexOfLastNonBlankLine := self findLast:[:line | line notEmptyOrNil and:[line isBlank not]].
    indexOfLastNonBlankLine == 0 ifTrue:[ ^ self copyEmpty ].
    indexOfLastNonBlankLine == self size ifTrue:[ ^ self ].
    ^ self copyTo:indexOfLastNonBlankLine

    "
'1
2
3' asStringCollection withoutTrailingBlankLines     
    "

    "
'
2
3
' asStringCollection withoutTrailingBlankLines       
    "

    "
'

' asStringCollection withoutTrailingBlankLines      
    "
! !

!StringCollection methodsFor:'printing & storing'!

printOn:aStream
    "print myself on aStream with embedded cr's"

    self do:[:eachString|
        eachString printOn:aStream.
        aStream cr.
    ].
!

printString
    "return the receivers printString"

    ^ self asString
! !

!StringCollection methodsFor:'queries'!

encoding
    self do:[:l | l notNil ifTrue:[^ l encoding]].
    "/ sigh
    ^ #'unicode'
! !

!StringCollection methodsFor:'searching'!

indexOfLineStartingWith:aString
    "return the index of the first line starting with the argument, aString"

    |index "{ Class:SmallInteger }" 
     l|

    index := 1.
    [index <= self size] whileTrue:[
        l := self at:index.
        (l notNil and:[l startsWith:aString]) ifTrue:[
            ^ index
        ].
        index := index + 1
    ].
    ^ 0

    "Modified: 24.2.1996 / 19:08:47 / cg"
! !

!StringCollection methodsFor:'special converting'!

withTabs
    "return a new stringCollection consisting of the receivers lines,
     where leading spaces are replaced by tabulator characters (assuming 8-col tabs).
     Notice: lines which do not contain leading spaces, are copied by reference to the
             new stringCollection (i.e. shared);
             otherwise new strings is created.
     Limitation: only the very first spaces are replaced"

    ^ self collect:[:string|
        string notNil ifTrue:[
            string withTabs     
        ] ifFalse:[
            string
        ]
    ]

    "
       ('        abcd            ') asStringCollection withTabs
    "

    "Created: 4.3.1996 / 17:09:07 / cg"
    "Modified: 4.3.1996 / 17:10:37 / cg"
!

withTabsExpanded
    "return a new stringCollection consisting of the receivers lines,
     where tabs are replaced by space characters (assuming 8-col tabs).
     Notice: lines which do not contain any tab, are copied by reference to the
             new stringCollection (i.e. shared);
             otherwise new strings is created."

    ^ self collect:[:string|
        string notNil ifTrue:[
            string withTabsExpanded     
        ] ifFalse:[
            string
        ]
    ]

    "
       |tab|
       tab := String with:Character tab.
       ('abcd', tab, 'tef', tab, 'tgh') asStringCollection withTabsExpanded
    "

    "Created: 12.2.1996 / 22:25:56 / stefan"
    "Modified: 14.2.1996 / 11:13:01 / stefan"
    "Modified: 4.3.1996 / 17:10:22 / cg"
! !

!StringCollection methodsFor:'testing'!

isStringCollection
    "return true, if the receiver is some kind of stringCollection;
     true is returned here - the method is redefined from Object."

    ^ true


! !

!StringCollection class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/StringCollection.st,v 1.40 2009-05-14 10:06:39 cg Exp $'
! !