TwoByteString.st
author claus
Mon, 06 Feb 1995 00:38:45 +0100
changeset 235 d8e62525bfdf
parent 97 b876f90648aa
child 256 f59b4cfdc55a
permissions -rw-r--r--
*** empty log message ***

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

AbstractString subclass:#TwoByteString
       instanceVariableNames:''
       classVariableNames:''
       poolDictionaries:''
       category:'Collections-Text'
!

TwoByteString comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	     All Rights Reserved

$Header: /cvs/stx/stx/libbasic/TwoByteString.st,v 1.9 1995-02-05 23:38:45 claus Exp $
'!

!TwoByteString class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/TwoByteString.st,v 1.9 1995-02-05 23:38:45 claus Exp $
"
!

documentation
"
    TwoByteStrings are like strings, but storing 16bits per character.
    The integration of them into the system is not completed ....
"
! !

!TwoByteString class methodsFor:'instance creation'!

basicNew:anInteger
    "return a new empty string with anInteger characters"

    ^ (super basicNew:(anInteger*2)) atAllPut:(Character space)
!

fromJISString:aString
    "return a new string containing the characters of aString,
     which are taken as JIS encoded."

    |newString sz dstIdx singleBytes start stop n1 n2 n3 b1 b2 val|

    sz := aString size.
    newString := self new:sz.
    sz ~~ 0 ifTrue:[
	dstIdx := 1.
	start := 1.
	singleBytes := true.

	[true] whileTrue:[
	    "scan for next escape"
	    stop := aString indexOf:(Character esc) startingAt:start.
	    stop == 0 ifTrue:[
		stop := sz + 1.
	    ] ifFalse:[
		(stop + 2) > sz ifTrue:[
		    stop := sz + 1.
		]
	    ].
	    singleBytes ifTrue:[
		newString replaceFrom:dstIdx to:(dstIdx + (stop - start - 1))
				 with:aString startingAt:start.
		dstIdx := dstIdx + (stop - start).
	    ] ifFalse:[
		start to:(stop - 1) by:2 do:[:i |
		    b1 := (aString at:i) asciiValue.
		    b2 := (aString at:i+1) asciiValue.
		    val := (b1 bitShift:8) bitOr:b2.
		    newString at:dstIdx put:(Character value:val).
		    dstIdx := dstIdx + 1.
		]
	    ].

	    stop > sz ifTrue:[
		^ newString copyFrom:1 to:dstIdx - 1.
	    ].
	    start := stop.

	    "
	     found an escape (at index stop) - check for ESC $ B
	    "
	    n1 := aString at:start.
	    n2 := aString at:(start + 1).
	    n3 := aString at:(start + 2).

	    (n2 == $$ and:[n3 == $B]) ifTrue:[
		singleBytes := false.
	    ] ifFalse:[
		(n2 == $( and:[n3 == $B]) ifTrue:[
		    singleBytes := true.
		] ifFalse:[
		    newString at:dstIdx put:n1.
		    newString at:(dstIdx + 1) put:n2.
		    newString at:(dstIdx + 2) put:n3.
		    dstIdx := dstIdx + 3.
		]
	    ].
	    start := start + 3.
	    start > sz ifTrue:[
		^ newString copyFrom:1 to:dstIdx-1.
	    ]
	]
    ].
    ^ newString

    "
     TwoByteString fromJISString:'hello'

     |s|
     s := 'hello' copyWith:Character esc.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$A.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$A.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$B.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$B.
     s := s , '$N'.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$B.
     s := s , '$N4A;z'.
     TwoByteString fromJISString:s

     |s|
     s := 'hello' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$B.
     s := s , '$N'.
     s := s copyWith:Character esc.
     s := s copyWith:$(.
     s := s copyWith:$B.
     s := s , 'hello'.
     TwoByteString fromJISString:s

     |s t l|
     s := 'kterm ' copyWith:Character esc.
     s := s copyWith:$$.
     s := s copyWith:$B.
     s := s , '$N4A;zC<Kv%(%_%e%l!!<%?'.
     s := s copyWith:Character esc.
     s := s copyWith:$(.
     s := s copyWith:$B.
     s := s , ' kterm'.
     t := TwoByteString fromJISString:s.
     l := Label new.
     l label:t.
     l font:(Font family:'k14' face:nil style:nil size:nil).
     l realize
    "
! !

!TwoByteString methodsFor:'queries'!

basicSize
    "return the size of the receiver.
     (i.e. the number of characters in this String)"

    ^ super basicSize // 2
! !
    
!TwoByteString methodsFor:'accessing'!

basicAt:index
    "return the character at position index, an Integer
     - reimplemented here since we return 16-bit characters"

    |val i|

    i := (index * 2) - 1.
    "always msb first"
    val := (super basicAt:(i+1)) + ((super basicAt:i) * 256).
    ^ Character value:val
!

basicAt:index put:aCharacter
    "store the argument, aCharacter at position index, an Integer
     - reimplemented here since we store 16-bit characters"

    |val i|
    val := aCharacter asciiValue.
    i := (index * 2) - 1.
    "always msb first"
    super basicAt:(i+1) put:(val bitAnd:16rFF).
    super basicAt:i put:(val // 256).
    ^ aCharacter
! !