MCScanner.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Nov 2006 14:06:28 +0100
changeset 40 34febde6d331
child 225 4453a8f6fb4a
permissions -rw-r--r--
initial checkin

"{ Package: 'stx:goodies/monticello' }"

Object subclass:#MCScanner
	instanceVariableNames:'stream'
	classVariableNames:''
	poolDictionaries:''
	category:'Monticello-Chunk Format'
!


!MCScanner class methodsFor:'as yet unclassified'!

scan: aStream
	^ (self new stream: aStream) next
!

scanTokens: aString
	"compatibility"
	^ Array with: (self scan: aString readStream)
! !

!MCScanner methodsFor:'as yet unclassified'!

next
	| c |
	stream skipSeparators.
	c _ stream peek.
	c = $# ifTrue: [c _ stream next; peek].
	c = $' ifTrue: [^ self nextString].
	c = $( ifTrue: [^ self nextArray].
	c isAlphaNumeric ifTrue: [^ self nextSymbol].
	self error: 'Unknown token type'.	
!

nextArray
	stream next. "("
	^ Array streamContents:
		[:s |
		[stream skipSeparators.
		(stream peek = $)) or: [stream atEnd]] whileFalse: [s nextPut: self next].
		stream next = $) ifFalse: [self error: 'Unclosed array']]
!

nextString
	^ stream nextDelimited: $'
!

nextSymbol
	^ (String streamContents:
		[:s |
		[stream peek isAlphaNumeric] whileTrue: [s nextPut: stream next]]) asSymbol
			
!

stream: aStream
	stream _ aStream
! !

!MCScanner class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCScanner.st,v 1.1 2006-11-22 13:06:28 cg Exp $'
! !