support/Xtreams__STXEncoder.st
author mkobetic
Tue, 31 Jan 2012 03:46:52 +0000
changeset 89 208ac7c53cfb
child 92 c5019e8f9992
permissions -rw-r--r--
added STXEncoder (utf8 support)

"{ Package: 'stx:goodies/xtreams/support' }"

"{ NameSpace: Xtreams }"

Encoder subclass:#STXEncoder
	instanceVariableNames:'encoder stream character contentsSpecies'
	classVariableNames:''
	poolDictionaries:''
	category:'Xtreams-Support'
!

STXEncoder comment:'Provides access to all encodings supported by VisualWorks.

Instance Variables
	encoder <StreamEncoder> the encoder from classic EncodedStream
	skipRecord      <PositionRecord> the skipRecord of the encoder to allow repeated decoding attempts
	backupRecord    <PositionRecord> snapshot of the skipRecord that we can restore from

'
!


!STXEncoder class methodsFor:'instance creation'!

encoder: anEncoder

	^self new encoder: anEncoder
!

for: anEncoding

	^self new encoding: anEncoding
! !

!STXEncoder class methodsFor:'class initialization'!

initialize

	DialectEncoder := self
! !

!STXEncoder methodsFor:'accessing'!

decodeFrom: aReadStream

        stream := aReadStream.
        ^encoder readNextCharacterFrom: self
!

encode: aCharacter on: aWriteStream

        character := aCharacter.
        ^aWriteStream write: (encoder readNextInputCharacterFrom: self)
!

encoder

	^encoder
!

next: count

        |bytes|

        bytes := ByteArray new: count.
        character isNil
                ifTrue: [ stream read: count into: bytes ]
                ifFalse: [ bytes at: 1 put: character.
                        character := nil.
                        stream read: count - 1 into: bytes at: 2 ].
        ^bytes
!

nextUnsignedShortMSB: bigEndian

        ^character codePoint
!

peek

        ^character ifNil: [ character := stream get ]
! !

!STXEncoder methodsFor:'initialize-release'!

encoder: anEncoder

        encoder := anEncoder.
        contentsSpecies := (anEncoder newString: 1) class.
!

encoding: anEncoding

        | newEncoder |
        newEncoder := CharacterEncoder encoderFor: anEncoding.
        newEncoder isNullEncoder ifTrue: [ self error: 'Unsupported encoding!!' ].
        self encoder: newEncoder
! !

!STXEncoder class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !

STXEncoder initialize!