PPToken.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 05 May 2012 00:02:49 +0200
changeset 28 1194e560eda4
parent 4 90de244a7fa2
child 30 6d6315787d46
permissions -rw-r--r--
Checkin from browser

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

Object subclass:#PPToken
	instanceVariableNames:'collection start stop'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitParser-Core'
!

PPToken comment:'PPToken represents a parsed part of the input stream. Contrary to a simple String it remembers where it came from, the original collection and its start and stop position.
Instance Variables:
	collection      <SequenceableCollection>        The collection this token comes from.
	start   <Integer>       The start position in the collection.
	stop    <Integer>       The stop position in the collection.'
!


!PPToken class methodsFor:'instance creation'!

new
	self error: 'Token can only be created using a dedicated constructor.'
!

on: aSequenceableCollection
	^ self on: aSequenceableCollection start: 1 stop: aSequenceableCollection size
!

on: aSequenceableCollection start: aStartInteger stop: aStopInteger
	^ self basicNew
		initializeOn: aSequenceableCollection
		start: aStartInteger stop: aStopInteger
! !

!PPToken methodsFor:'accessing'!

collection
	"Answer the underlying collection of this token."

	^ collection
!

size
	"Answer the size of this token."

	^ stop - start + 1
!

start
	"Answer the start position of this token in the underlying collection."

	^ start
!

stop
	"Answer the stop position of this token in the underlying collection."

	^ stop
!

value
	"Answer the contents of this token."

	^ collection copyFrom: start to: stop
! !

!PPToken methodsFor:'comparing'!

= anObject
	^ self class = anObject class and: [ self value = anObject value ]
!

hash
	^ self value hash
! !

!PPToken methodsFor:'copying'!

copyFrom: aStartInteger to: aStopInteger
	^ self class on: collection start: start + aStartInteger - 1 stop: stop + aStopInteger - 3
! !

!PPToken methodsFor:'initialization'!

initializeOn: aSequenceableCollection start: aStartInteger stop: aStopInteger
	collection := aSequenceableCollection.
	start := aStartInteger.
	stop := aStopInteger
! !

!PPToken methodsFor:'printing'!

printOn: aStream
	super printOn: aStream.
	aStream nextPut: $(; nextPutAll: self value; nextPut: $)
! !

!PPToken methodsFor:'private'!

newline
	"Parser a platform independent newline sequence. LF: Unix, CR+LF: Windows, and CR: Apple."

	^ (Character lf asParser)
	/ (Character cr asParser , Character lf asParser optional)
! !

!PPToken methodsFor:'querying'!

column
	"Answer the column number of this token in the underlying collection."

	| position |
	position := 0.
	(self newline , [ :stream |
		start <= stream position
			ifTrue: [ ^ start - position ].
		position := stream position ] asParser
		/ #any asParser) star
			parse: collection.
	 ^ start - position
!

line
	"Answer the line number of this token in the underlying collection."

	| line |
	line := 1.
	(self newline , [ :stream |
		start <= stream position
			ifTrue: [ ^ line ].
		line := line + 1 ] asParser
		/ #any asParser) star
			parse: collection.
	^ line
! !

!PPToken class methodsFor:'documentation'!

version_SVN
    ^ '$Id: PPToken.st,v 1.2 2012-01-13 11:22:50 cg Exp $'
! !