PPToken.st
author Claus Gittinger <cg@exept.de>
Wed, 20 Mar 2013 19:46:56 +0100
changeset 135 39ad8d5dfd95
parent 91 ed96c98bff4a
child 160 24352e941a6d
permissions -rw-r--r--
removed via FileBrowser

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

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


!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."

        Smalltalk isSmalltalkX ifTrue:[
            ^ (Character lf asParser)
            / (Character return asParser , Character lf asParser optional)
        ] ifFalse:[
            ^ (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
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.4 2012-12-01 14:27:17 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.4 2012-12-01 14:27:17 cg Exp $'
!

version_SVN
    ^ '§Id: PPToken.st 2 2010-12-17 18:44:23Z vranyj1 §'
! !