Unicode32String.st
author Claus Gittinger <cg@exept.de>
Thu, 04 Dec 2014 18:43:03 +0100
changeset 3454 75415b0c4625
parent 3065 8488543e42fa
child 3663 2c9a059e292d
permissions -rw-r--r--
class: Unicode32String comment/format in: #asSymbolIfInterned

"
 COPYRIGHT (c) 2004 by eXept Software AG 
              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:libbasic2' }"

FourByteString variableLongSubclass:#Unicode32String
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text'
!

!Unicode32String class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 by eXept Software AG 
              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
"
    Not yet fully finished - unicode support is still being implemented.
"
! !

!Unicode32String class methodsFor:'initialization'!

initialize
    "initialize the class - private"

    self flags:(Behavior flagLongs)

    "
     Unicode32String initialize
    "

    "Created: 30.6.1997 / 15:35:52 / cg"
    "Modified: 30.6.1997 / 15:39:21 / cg"
! !

!Unicode32String class methodsFor:'reading'!

readFrom:aStreamOrString onError:exceptionBlock
    "read & return the next String from the (character-)stream aStream;
     skipping all whitespace first; return the value of exceptionBlock,
     if no string can be read. The sequence of characters as read from the
     stream must be one as stored via storeOn: or storeString."

    "
     this method is not to be inherited
     (i.e. not ok for subclasses; Symbol, for example)
    "
    self ~~ Unicode32String ifTrue:[
        ^ super readFrom:aStreamOrString onError:exceptionBlock
    ].
    ^ self readSmalltalkStringFrom:aStreamOrString onError:exceptionBlock

    "
        self readFrom:'abcäöü' storeString
        String readFrom:'abcäöü' storeString
    "
! !


!Unicode32String methodsFor:'conversion'!

asSymbolIfInterned
    "If a symbol with the receiver's characters is already known, return it. Otherwise, return nil. 
     Because ST/X does not support non-8-bit symbols, this method
     has been redefined to only return a symbol, if the receiver does NOT contain
     any non-8 bit characters."

    |s|

    Error catch:[
        s := self asSingleByteString.
    ].
    s isNil ifTrue:[^ s].
    ^ s asSymbolIfInterned
!

asUnicode32String
    "as the receiver already is a unicode-32 string, return it"

    ^ self
!

asUnicodeString
    "as the receiver already is a unicode string, return it"

    ^ self
!

printOn:aStream
    "print the receiver on aStream. 
     Let aStream decide how to represent this, whether utf8, ucs16, ..."

    aStream nextPutAllUnicode:self

    "Modified (comment): / 27-07-2013 / 15:37:03 / cg"
! !

!Unicode32String methodsFor:'printing & storing'!

storeOn:aStream
    "put the storeString of myself on aStream"

    (self utf8Encoded storeOn:aStream).
    aStream nextPutAll:' utf8Decoded'.
"/    aStream nextPut:$'.
"/    (self includes:$') ifTrue:[
"/        self do:[:thisChar |
"/            (thisChar == $') ifTrue:[aStream nextPut:thisChar].
"/            aStream nextPutUnicode:thisChar
"/        ]
"/    ] ifFalse:[
"/        aStream nextPutAllUnicode:self
"/    ].
"/    aStream nextPut:$'

    "Modified: / 28-09-2011 / 16:18:43 / cg"
!

storeString
    "return a String for storing myself"

"/    ^ self basicStoreString.
"/    ^ (self withCEscapes storeString),' withoutCEscapes'.
    ^ (self utf8Encoded storeString),' utf8Decoded'.

    "Modified: / 25-01-2012 / 11:59:26 / cg"
!

unicodeStoreOn:aStream
    "put the storeString of myself on aStream"

    aStream nextPut:$'.
    (self includes:$') ifTrue:[
        self do:[:thisChar |
            (thisChar == $') ifTrue:[aStream nextPut:thisChar].
            aStream nextPutUnicode:thisChar
        ]
    ] ifFalse:[
        aStream nextPutAllUnicode:self
    ].
    aStream nextPut:$'
!

unicodeStoreString
    "return a UnicodeString for storing myself.
     This method is a kind of kludge.
     Use it when you want to write a storeString to an encoded Stream"

    ^ self basicStoreString.
! !

!Unicode32String methodsFor:'testing'!

isUnicode32String
    ^ true
!

isUnicodeString
    ^ true
! !

!Unicode32String class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Unicode32String.st,v 1.15 2014-12-04 17:43:03 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/Unicode32String.st,v 1.15 2014-12-04 17:43:03 cg Exp $'
! !


Unicode32String initialize!