Text.st
author ca
Wed, 12 Jun 1996 13:35:16 +0200
changeset 395 30c7f6a7c9bb
parent 394 26ea25797eae
child 404 14cf34141532
permissions -rw-r--r--
class string:runs

"
 COPYRIGHT (c) 1996 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.
"


CharacterArray subclass:#Text
	instanceVariableNames:'string runs'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text'
!

!Text class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 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
"
    Texts add emphasis information to a string.
    Texts and strings should behave interchanchably to the outside
    world, except that texts keep per-character emphasis information.
    (strings return nil, when asked for an elements emphasis).
    Use #string, to get a texts underlying string without any emphasis
    information.

    Currently, the following attributes are supported:
        #bold     
        #italic  
        #underline  
        #strikeout
        (#color -> aColor)
        (#backgroundColor -> aColor)

    Attributes may be combined (pass an array of above) as emphasis.
    See examples.

    This class is not yet fully implemented - being constructed.

    [author:]
        Claus Gittinger

    [see also:]
        CharacterArray String RunArray
"
!

examples
"
  plain string (for comparison):
                                                                        [exBegin]
    Dialog
        warn:'hello'
                                                                        [exEnd]


  emphasized strings as dialog titles:
                                                                        [exBegin]
    Dialog
        warn:((Text string:'hello') allBold)
                                                                        [exEnd]
                                                                        [exBegin]
    Dialog
        warn:(Text string:'hello' emphasis:#italic)
                                                                        [exEnd]
                                                                        [exBegin]
    Dialog
        warn:(Text string:'hello' emphasis:#(bold underline))
                                                                        [exEnd]
                                                                        [exBegin]
    Dialog
        warn:(Text string:'hello' 
                 emphasis:(Array with:#bold
                                 with:#strikeout
                                 with:(#color->Color red)))
                                                                        [exEnd]
                                                                        [exBegin]
    Dialog
        warn:(Text string:'hello' 
                 emphasis:(Array with:#bold
                                 with:#strikeout
                                 with:(#color->Color red)
                                 with:(#backgroundColor->Color yellow)))
                                                                        [exEnd]
                                                                        [exBegin]
    Dialog
        warn:(Text string:'hello' color:(Color red))
                                                                        [exEnd]


  in an editTextView:
                                                                        [exBegin]
    |t v|

    t := 'The quick brown fox jumps over the lazy dog' asText.
    t emphasizeFrom:(t findString:'quick') count:5 with:#bold.
    t emphasizeFrom:(t findString:'brown') count:9 
                                         with:(Array with:#color->(Color name:'brown')
                                                     with:#bold).
    t emphasizeFrom:(t findString:'lazy') count:4 
                                          with:(Array with:#color->(Color red)
                                                      with:#italic).
    t emphasizeFrom:(t findString:'dog') count:3 with:#underline.

    v := HVScrollableView for:EditTextView.
    v contents:t.

    v width:450.
    v open.
                                                                        [exEnd]
"
! !

!Text class methodsFor:'initialization'!

initialize
    "initialize the class"

    "
     consider this a kludge:
     I want to inherit behavior from CharacterArray, but not
     its implementation (indexed access).
    "

    self flags:(Behavior flagRegular)

    "
     Text initialize
    "

    "Modified: 12.5.1996 / 17:53:50 / cg"
! !

!Text class methodsFor:'instance creation'!

fromString:aString 
    "create a Text instance, for the characters in aString,
     without emphasis."

    ^ self new string:aString emphasis:nil

    "
     Text fromString:'hello'
    "

    "Modified: 12.5.1996 / 17:05:34 / cg"
!

new:size
    "create a new empty Text instance.
     Redefined for string-protocol compatibility"

    ^ self string:(String new:size)

    "Created: 12.5.1996 / 11:57:27 / cg"
    "Modified: 12.5.1996 / 17:05:17 / cg"
!

string:aString 
    "create a Text instance, for the characters in aString,
     without emphasis."

    ^ self new string:aString emphasis:nil

    "
     Text string:'hello'
    "

    "Modified: 12.5.1996 / 17:05:00 / cg"
!

string:aString color:aColor
    "create a Text instance, for the characters in aString,
     which are colored as aColor (only the foregroundColor is affected).
     This is a shortCut for creating an emphasis of #color->aColor)"

    ^ self new string:aString emphasis:(#color->aColor)

    "
     Dialog
        information:(Text string:'hello' color:(Color red))
    "

    "Created: 12.5.1996 / 17:03:20 / cg"
    "Modified: 16.5.1996 / 12:37:46 / cg"
!

string:aString emphasis:attribute
    "create a Text instance, for the characters in aString,
     which are emphasized as described by attribute."

    ^ self new string:aString emphasis:attribute

    "
     Text string:'hello' emphasis:#bold

     Dialog
        information:(Text string:'hello' emphasis:#bold)

     Dialog
        information:(Text string:'hello' emphasis:#italic)

     Dialog
        information:(Text string:'hello' emphasis:#underline)

     Dialog
        information:(Text string:'hello' emphasis:#strikeout)
    "

    "Modified: 12.5.1996 / 17:16:03 / cg"
!

string:aString emphasisCollection:attributeCollection
    "create a Text instance, for the characters in aString,
     which are individually emphasized as described by attributeCollection."

    ^ self new string:aString emphasisCollection:attributeCollection

    "
     Text 
        string:'hello' 
        emphasisCollection:#(#bold #bold #italic #italic #italic)

     Dialog
        information:(Text 
                        string:'hello' 
                        emphasisCollection:#(#bold #bold #italic #italic #(#underline italic)))
    "

    "Created: 14.5.1996 / 14:02:18 / cg"
    "Modified: 14.5.1996 / 15:01:28 / cg"
!

string:aString foregroundColor:fgColor backgroundColor:bgColor
    "create a Text instance, for the characters in aString,
     which are colored in fgColor on bgColor.
     This is a shortCut for creating an emphasis of 
     #( #color->fgColor) (#backgroundColor->bgColor)"

    ^ self new 
        string:aString 
        emphasis:(Array with:#color->fgColor
                        with:#backgroundColor->bgColor)

    "
     Dialog
        information:(Text string:'hello' 
                          foregroundColor:(Color red)
                          backgroundColor:(Color yellow))
    "

    "Modified: 11.5.1996 / 14:21:01 / cg"
    "Created: 16.5.1996 / 12:37:24 / cg"
!

string:aString runs:aRun
    "create a Text instance, for the characters in aString,
     which are individually emphasized as described by attributeCollection."

    ^ self new string:aString emphasisCollection:aRun.
! !

!Text class methodsFor:'emphasis helper'!

addEmphasis:e1 to:e2
    "merge two emphasis's into one"

    |ne|

    e1 isNil ifTrue:[^ e2].
    e2 isNil ifTrue:[^ e1].
    e1 == e2 ifTrue:[^ e1].

    (e1 isSymbol 
     or:[e1 isAssociation]) ifTrue:[
        (e2 isSymbol 
         or:[e2 isAssociation]) ifTrue:[
            ^ Array with:e1 with:e2
        ].
        (e2 includes:e1) ifTrue:[^ e2].
        ^ e2 copyWith:e1
    ].
    (e2 isSymbol 
     or:[e2 isAssociation]) ifTrue:[
        (e1 includes:e2) ifTrue:[^ e1].
        ^ e1 copyWith:e2
    ].
    "/ ould use:
    "/    ^ (e1 asSet addAll:e2; asArray)

    "/ but we do it manually, to preserve the
    "/ order. (should create longer runs, while editing)

    ne := e1.
    e2 do:[:e |
        (ne includes:e) ifFalse:[
           ne := ne copyWith:e
        ]
    ].
    ^ ne.

    "
     Text addEmphasis:#bold to:#bold           
     Text addEmphasis:#bold to:#italic         
     Text addEmphasis:#bold to:#(italic strikeout)   
     Text addEmphasis:#italic to:#(italic strikeout) 
     Text addEmphasis:#(italic strikeout) to:#bold  
     Text addEmphasis:#(italic strikeout) to:#italic 
     Text addEmphasis:#(italic strikeout) to:#(bold underline) 
     Text addEmphasis:(#color->Color red) to:#(bold underline) 
    "

    "Modified: 14.5.1996 / 17:15:44 / cg"
!

emphasis:e1 includes:e2
    "return true, if e1 includes e2.
     e2 should be a single emphasis."

    |ne|

    e1 isNil ifTrue:[^ false].
    e2 isNil ifTrue:[^ false].
    e1 == e2 ifTrue:[^ true].

    (e1 isSymbol 
     or:[e1 isAssociation]) ifTrue:[
        ^ false
    ].
    (e2 isSymbol 
     or:[e2 isAssociation]) ifTrue:[
        ^ (e1 includes:e2)
    ].
    ^ false

    "
     Text emphasis:#bold includes:#bold           
     Text emphasis:#bold includes:#ialic         
     Text emphasis:#(italic strikeout) includes:#bold  
     Text emphasis:#(italic strikeout) includes:#italic 
    "

    "Modified: 14.5.1996 / 17:45:11 / cg"
!

removeEmphasis:e1 from:e2
    "remove an emphasis; if it was not in e1, do nothing"

    |ne|

    e1 isNil ifTrue:[^ nil].
    e2 isNil ifTrue:[^ e1].
    e1 == e2 ifTrue:[^ nil].

    (e2 isSymbol 
     or:[e2 isAssociation]) ifTrue:[
        (e1 includes:e2) ifTrue:[^ nil].
        ^ e2
    ].
    (e1 isSymbol 
     or:[e1 isAssociation]) ifTrue:[
        (e2 includes:e1) ifTrue:[
            ne := e2 copyWithout:e1.
            ne size == 1 ifTrue:[^ ne at:1].
            ne size == 0 ifTrue:[^ nil].
            ^ ne
        ].
        ^ e2
    ].

    "/ ould use:
    "/    ^ (e2 asSet removeAll:e1; asArray)

    "/ but we do it manually, to preserve the
    "/ order. (should create longer runs, while editing)

    ne := e2.
    e1 do:[:e |
        (ne includes:e) ifTrue:[
           ne := ne copyWithout:e
        ]
    ].
    ne size == 1 ifTrue:[^ ne at:1].
    ne size == 0 ifTrue:[^ nil].
    ^ ne.

    "
     Text removeEmphasis:#bold from:#bold           
     Text removeEmphasis:#bold from:#italic         
     Text removeEmphasis:#bold from:#(italic strikeout)   
     Text removeEmphasis:#italic from:#(italic strikeout) 
     Text removeEmphasis:#(italic strikeout) from:#bold  
     Text removeEmphasis:#(italic strikeout) from:#italic  
     Text removeEmphasis:#(italic strikeout) from:#(bold underline) 
     Text removeEmphasis:#(italic strikeout bold) from:#(bold underline) 
     Text removeEmphasis:#(italic strikeout bold underline) from:#(bold underline) 
     Text removeEmphasis:(#color->Color red) from:#(bold underline) 
    "

    "Modified: 14.5.1996 / 17:23:46 / cg"
! !

!Text methodsFor:'comparing'!

= aStringOrText
    "compare the receiver and the argument, ignoring emphasis"

    aStringOrText isString ifFalse:[^ false].
    ^ string = aStringOrText string


    "
     'hello' asText = 'hello'        
     'hello' asText = 'hello' asText 
     'hello' asText allBold = 'hello' 
    "

    "Modified: 4.6.1996 / 11:14:58 / cg"
! !

!Text methodsFor:'converting'!

asText
    "return the receiver itself - it is already a text object"

    ^ self

    "Created: 11.5.1996 / 14:08:36 / cg"
    "Modified: 16.5.1996 / 11:15:12 / cg"
!

at:characterIndex
    "return the plain character at characterIndex"

    ^ string at:characterIndex

    "Created: 11.5.1996 / 14:25:41 / cg"
    "Modified: 16.5.1996 / 11:15:33 / cg"
!

at:characterIndex put:aCharacter
    "change the character at characterIndex to be aCharacter.
     The emphasis (if any) of that character remains unchanged."

    ^ string at:characterIndex put:aCharacter

    "Created: 11.5.1996 / 14:25:49 / cg"
    "Modified: 16.5.1996 / 11:15:57 / cg"
! !

!Text methodsFor:'copying'!

, aStringOrText
    "concatenate the receivers characters with the arguments characters, 
     and return string or text object containing those characters.
     If either the receiver or the argument contains emphasis information,
     a text object will be returned. Otherwise, a string (i.e. without emphasis)
     is returned."

    (aStringOrText hasChangeOfEmphasis 
    or:[self hasChangeOfEmphasis]) ifTrue:[
        ^ self species new
            string:(string , aStringOrText)
            emphasisCollection:(runs , aStringOrText emphasisCollection)
    ].
    ^ string , aStringOrText string

    "
     ('hello' asText allBold) , ' world'    
     'hello' , (' world' asText allBold)
     'hello' , ' world'
     ('hello' asText allBold) , (' world' asText allBold)
    "

    "Modified: 16.5.1996 / 11:17:40 / cg"
!

concatenateFromString:aString
    "return the concatenation of aString and myself.
     This may be a Text (if I have emphasis) or a string (if not)."

    self hasChangeOfEmphasis ifTrue:[
        ^ self species new
                string:(aString , string)
                emphasisCollection:((RunArray new:(aString size)) , runs).
    ].
    ^ aString , string

    "Modified: 14.5.1996 / 15:56:05 / cg"
!

postCopy
    string := string copy.
    runs := runs copy
! !

!Text methodsFor:'displaying'!

displayOn:aGC x:x y:y
    "display the receiver on a GC"

    self displayOn:aGC x:x y:y opaque:false

    "Modified: 12.5.1996 / 11:14:57 / cg"
!

displayOn:aGC x:x y:y from:start to:stop
    "display the receiver on a GC"

    "q&d hack"

    (self copyFrom:start to:stop) displayOn:aGC x:x y:y opaque:false

    "Modified: 12.5.1996 / 12:49:33 / cg"
!

displayOn:aGC x:x0 y:y opaque:opaque
    "display the receiver on a GC"

    |savedFont savedPaint savedBgPaint font color boldFont italicFont boldItalicFont 
     bgPaint
     bold italic underline strikeout 
     pos    "{ Class: SmallInteger }"
     endPos "{ Class: SmallInteger }"
     x      "{ Class: SmallInteger }"
     l      "{ Class: SmallInteger }"
     yL k value device|

    savedFont := aGC basicFont.
    savedPaint := aGC paint.
    savedBgPaint := aGC backgroundPaint.

    pos := 1.
    x := x0.
    runs runsDo:[:len :emphasis |
        color := nil.
        bold := italic := underline := strikeout := false.
        bgPaint := savedBgPaint.

        emphasis isSymbol ifTrue:[
            emphasis == #bold ifTrue:[bold := true]
            ifFalse:[emphasis == #italic ifTrue:[italic := true]
            ifFalse:[emphasis == #underline ifTrue:[underline := true]
            ifFalse:[emphasis == #strikeout ifTrue:[strikeout := true]
            ]]]
        ] ifFalse:[
            (emphasis isMemberOf:Association) ifTrue:[
                value := emphasis value.
                k := emphasis key.
                k == #color ifTrue:[
                    color := value
                ] ifFalse:[k == #backgroundColor ifTrue:[
                    bgPaint := value
                ]]
            ] ifFalse:[
                emphasis notNil ifTrue:[
                    emphasis do:[:entry |
                        entry == #bold ifTrue:[bold := true]
                        ifFalse:[entry == #italic ifTrue:[italic := true]
                        ifFalse:[entry == #underline ifTrue:[underline := true]
                        ifFalse:[entry == #strikeout ifTrue:[strikeout := true]
                        ifFalse:[
                            (entry isMemberOf:Association) ifTrue:[
                                value := entry value.
                                k := entry key.
                                k == #color ifTrue:[
                                    color := value
                                ] ifFalse:[k == #backgroundColor ifTrue:[
                                    bgPaint := value
                                ]]
                            ]
                        ]]]]
                    ]
                ]
            ]
        ].

        device := aGC graphicsDevice.

        color isNil ifTrue:[
            color := savedPaint.
        ] ifFalse:[
            color := color on:device.
        ].

        bold ifTrue:[
            italic ifTrue:[
                boldItalicFont isNil ifTrue:[
                    boldItalicFont := savedFont asBold asItalic on:device
                ].
                font := boldItalicFont.
            ] ifFalse:[
                boldFont isNil ifTrue:[
                    boldFont := savedFont asBold on:device
                ].
                font := boldFont.
            ]
        ] ifFalse:[
            italic ifTrue:[
                italicFont isNil ifTrue:[
                    italicFont := savedFont asItalic on:device
                ].
                font := italicFont.
            ] ifFalse:[
                font := savedFont
            ]
        ].
        aGC basicFont:font.
        aGC paint:color on:bgPaint.

        endPos := pos + len - 1.
        opaque ifTrue:[
            aGC displayOpaqueString:string from:pos to:endPos x:x y:y.
        ] ifFalse:[
            aGC displayString:string from:pos to:endPos x:x y:y.
        ].
        l := aGC font widthOf:string from:pos to:endPos.

        underline ifTrue:[
            yL := y+1.
            aGC displayLineFromX:x y:yL toX:x+l-1 y:yL
        ].
        strikeout ifTrue:[
            yL := y-(font ascent//2).
            aGC displayLineFromX:x y:yL toX:x+l-1 y:yL
        ].

        x := x + l.
        pos := endPos + 1
    ].

    aGC basicFont:savedFont.
    aGC paint:savedPaint on:savedBgPaint.

    "Created: 12.5.1996 / 11:14:30 / cg"
    "Modified: 28.5.1996 / 20:26:20 / cg"
!

displayOpaqueOn:aGC x:x y:y
    "display the receiver on a GC"

    self displayOn:aGC x:x y:y opaque:true

    "Modified: 12.5.1996 / 11:14:52 / cg"
!

displayOpaqueOn:aGC x:x y:y from:start to:stop
    "display the receiver on a GC"

    "q&d hack"

    (self copyFrom:start to:stop) displayOn:aGC x:x y:y opaque:true

    "Created: 12.5.1996 / 12:29:37 / cg"
    "Modified: 12.5.1996 / 12:49:19 / cg"
! !

!Text methodsFor:'emphasis'!

allBold
    "make all characters bold"

    runs := RunArray new:(string size) withAll:#bold

    "
     (Text string:'hello') allBold
    "

    "Modified: 11.5.1996 / 14:22:12 / cg"
!

emphasis
    "return the emphasis"

    ^ runs

    "
     (Text string:'hello') allBold emphasis 
     'hello' emphasis   
    "

    "Modified: 11.5.1996 / 14:22:31 / cg"
    "Created: 14.5.1996 / 13:59:03 / cg"
!

emphasisAt:characterIndex
    "return the emphasis at some index"

    ^ runs at:characterIndex

    "
     (Text string:'hello') allBold emphasisAt:2 
    "

    "Modified: 11.5.1996 / 14:22:31 / cg"
!

emphasisAt:characterIndex add:newEmphasis
    "add to the emphasis at some index. return the receiver"

    |e|

    e := runs at:characterIndex.
    e := self class addEmphasis:newEmphasis to:e.
    runs at:characterIndex put:e

    "
     (Text string:'hello') allBold emphasisAt:2 add:#italic
    "

    "Created: 14.5.1996 / 16:48:39 / cg"
    "Modified: 14.5.1996 / 17:13:47 / cg"
!

emphasisAt:characterIndex put:emphasis
    "change the emphasis at some index. return the receiver"

    runs at:characterIndex put:emphasis

    "
     (Text string:'hello') allBold emphasisAt:2 put:#italic
    "

    "Modified: 12.5.1996 / 12:40:31 / cg"
!

emphasisAt:characterIndex remove:emphasisToRemove
    "remove from the emphasis at some index. return the receiver"

    |e|

    e := runs at:characterIndex.
    e := self class removeEmphasis:emphasisToRemove from:e.
    runs at:characterIndex put:e

    "
     (Text string:'hello') 
        allBold emphasisAt:2 remove:#bold

     (Text string:'hello' emphasis:#(bold italic)) 
        emphasisAt:2 remove:#bold
    "

    "Created: 14.5.1996 / 16:48:39 / cg"
    "Modified: 14.5.1996 / 17:25:04 / cg"
!

emphasisCollection
    "return the emphasis"

    ^ runs

    "
     (Text string:'hello') allBold emphasis 
     'hello' emphasis   
    "

    "Created: 14.5.1996 / 13:59:03 / cg"
    "Modified: 14.5.1996 / 15:02:11 / cg"
!

emphasizeAllWith:emphasis
    "change the emphasis of all characters"

    runs := RunArray new:(string size) withAll:emphasis

    "
     (Text string:'hello') allBold emphasizeAllWith:#italic 
    "

    "Modified: 11.5.1996 / 14:22:52 / cg"
!

emphasizeFrom:start count:count with:emphasis
    "change the emphasis of a range of characters, given startIndex and count."

    self emphasizeFrom:start to:(start+count-1) with:emphasis

    "
     (Text string:'hello world') 
        emphasizeFrom:1 count:5 with:#bold;
        emphasizeFrom:7 count:5 with:#italic
    "

    "Modified: 11.5.1996 / 14:30:02 / cg"
    "Created: 16.5.1996 / 10:52:27 / cg"
!

emphasizeFrom:start to:stop with:emphasis
    "change the emphasis of a range of characters"

    |newRuns|

    newRuns := RunArray new.

    "/ for now - a q&d hack
    1 to:start-1 do:[:i |
        newRuns add:(runs at:i).
    ].
    newRuns add:emphasis withOccurrences:(stop - start + 1).
    stop+1 to:string size do:[:i |
        newRuns add:(runs at:i)
    ].
    runs := newRuns

    "
     (Text string:'hello world') 
        emphasizeFrom:1 to:5 with:#bold;
        emphasizeFrom:7 to:11 with:#italic
    "

    "Modified: 11.5.1996 / 14:30:02 / cg"
!

emphasizeFrom:start with:emphasis
    "change the emphasis of some characters upTo the end"

    self emphasizeFrom:start to:(self size) with:emphasis

    "
     (Text string:'hello world') 
        emphasizeFrom:1 count:5 with:#bold;
        emphasizeFrom:7 with:#italic
    "

    "Modified: 11.5.1996 / 14:30:02 / cg"
    "Created: 17.5.1996 / 15:15:32 / cg"
! !

!Text methodsFor:'printing & storing'!

printOn:aStream
    "print the receivers characters (including emphasis) on
     aStream. Notice, that some streams simply ignore the emphasis."

    "/ this could be implemented in a more efficient way ...

    self keysAndValuesDo:[:i :c |
        aStream emphasis:(self emphasisAt:i).
        aStream nextPut:c.
    ].

    "
     (notice: (currently) the Transcript ignores any emphasis ...)

     'hello world' printOn:Transcript.
     Transcript cr.
     'hello world' asText allBold printOn:Transcript.
     Transcript cr.
     ('hello world' asText emphasizeAllWith:#italic) printOn:Transcript.
     Transcript cr.
    "

    "Modified: 16.5.1996 / 11:23:04 / cg"
!

storeOn:aStream
    "append a printed representation from which the receiver can be reconstructed
     to aStream."

    aStream nextPutAll:'(Text string:'.
    string storeOn:aStream.
    aStream nextPutAll:' runs:'.
    runs storeOn:aStream.
    aStream nextPutAll:')'.

    "Created: 11.5.1996 / 14:27:09 / cg"
    "Modified: 16.5.1996 / 11:23:32 / cg"
! !

!Text methodsFor:'private accessing'!

string:aString emphasis:emphasis
    "set the string and emphasis. The emphasis is applied to all characters."

    string := aString.
    runs := RunArray new:string size withAll:emphasis

    "
     |t|

     t := Text new string:'hello' emphasis:#bold.
     t emphasisAt:2.
    "

    "Modified: 16.5.1996 / 11:24:03 / cg"
!

string:aString emphasisCollection:emphasisCollection
    "set the string and emphasis collection.
     The emphasis collection contains per-character information."

    string := aString.
    runs := emphasisCollection asRunArray

    "
     |t|

     t := Text new string:'hello' emphasisCollection:(#bold #bold #bold #italic #italic).
     t emphasisAt:2.
    "

    "Created: 14.5.1996 / 14:03:29 / cg"
    "Modified: 16.5.1996 / 11:24:21 / cg"
! !

!Text methodsFor:'queries'!

bitsPerCharacter
    "return the underlying strings bitsPerCharacter 
     (i.e. is it a regular String or a TwoByteString)"

    ^ string bitsPerCharacter

    "Created: 12.5.1996 / 15:44:04 / cg"
    "Modified: 16.5.1996 / 11:24:54 / cg"
!

hasChangeOfEmphasis
    "return true, if the receiver contains non-empty emphasis information"

    ^ (runs notNil
       and:[(runs findFirst:[:e | e notNil]) ~~ 0])

    "Created: 11.5.1996 / 14:03:19 / cg"
    "Modified: 14.5.1996 / 15:51:01 / cg"
!

heightOn:aGC
    "return the number of device units, required on aGC's device"

    ^ aGC font heightOf:string

    "Created: 12.5.1996 / 11:02:03 / cg"
!

indexOf:aCharacter startingAt:index
    "search aCharacters index in the underlying string"

    ^ string indexOf:aCharacter startingAt:index

    "Created: 11.5.1996 / 13:58:56 / cg"
    "Modified: 16.5.1996 / 11:25:12 / cg"
!

isText
    "return true if this is a Text object - always true here"

    ^ true

    "Created: 12.5.1996 / 10:56:24 / cg"
    "Modified: 16.5.1996 / 11:25:29 / cg"
!

occurrencesOf:aCharacter
    "count & return the number of occurrences of aCharacter in the 
     underlying string"

    ^ string occurrencesOf:aCharacter

    "Created: 11.5.1996 / 13:58:46 / cg"
    "Modified: 16.5.1996 / 11:25:51 / cg"
!

size
    "return the number of characters in the underlying string"

    ^ string size

    "Created: 11.5.1996 / 14:25:15 / cg"
    "Modified: 16.5.1996 / 11:26:08 / cg"
!

string
    "return the receiver without any emphasis information
     i.e. the underlying string."

    ^ string

    "Created: 11.5.1996 / 13:58:38 / cg"
    "Modified: 16.5.1996 / 11:26:30 / cg"
!

widthOn:aGC
    "return the number of device units, required on aGC's device"

    |savedFont savedPaint boldFont italicFont bold italic pos f l device|

    savedFont := aGC basicFont on:aGC device.

    pos := 1.
    l := 0.
    runs runsDo:[:len :emphasis |
        emphasis isSymbol ifTrue:[
            bold := emphasis == #bold.
            italic := emphasis == #italic.
        ] ifFalse:[
            (emphasis isNil 
            or:[emphasis isMemberOf:Association]) ifTrue:[
                bold := italic := false
            ] ifFalse:[
                bold := emphasis includesIdentical:#bold.
                italic := emphasis includesIdentical:#italic.
            ]
        ].

        device := aGC graphicsDevice.
        bold ifTrue:[
            boldFont isNil ifTrue:[
                boldFont := savedFont asBold on:device
            ].
            f := boldFont.
        ] ifFalse:[
            italic ifTrue:[
                italicFont isNil ifTrue:[
                    italicFont := savedFont asItalic on:device
                ].
                f := italicFont
            ] ifFalse:[
                f := savedFont
            ]
        ].
        l := l + (f widthOf:string from:pos to:(pos + len - 1)).
        pos := pos + len
    ].

    ^ l

    "Modified: 28.5.1996 / 20:26:46 / cg"
! !

!Text methodsFor:'replacing'!

replaceFrom:start to:stop with:aCollection startingAt:startIndex
    "replace a range of characters, from another string or text object.
     The corresponding characters' emphasis information is also copied."

    |idx|

    aCollection isString ifTrue:[
        aCollection hasChangeOfEmphasis ifTrue:[
            string replaceFrom:start to:stop with:aCollection startingAt:startIndex.
            idx := startIndex.
            start to:stop do:[:col |
                self emphasisAt:col put:(aCollection emphasisAt:idx).
                idx := idx + 1.
            ].
            ^ self.
        ]
    ].

    string replaceFrom:start to:stop with:aCollection startingAt:startIndex.
    self emphasizeFrom:start to:stop with:nil

    "
     ((Text string:'hello') allBold emphasisAt:2 put:#italic)
        copyFrom:1 to:3
    "

    "Modified: 16.5.1996 / 11:27:19 / cg"
! !

!Text class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Text.st,v 1.21 1996-06-12 11:35:16 ca Exp $'
! !
Text initialize!