class: PPToken
authorClaus Gittinger <cg@exept.de>
Tue, 04 Mar 2014 15:32:08 +0100
changeset 160 24352e941a6d
parent 159 0a53379a1214
child 161 798f60fd396a
class: PPToken class definition added:5 methods comment/format in: #size changed:8 methods
PPToken.st
--- a/PPToken.st	Tue Mar 04 15:32:00 2014 +0100
+++ b/PPToken.st	Tue Mar 04 15:32:08 2014 +0100
@@ -1,13 +1,26 @@
 "{ Package: 'stx:goodies/petitparser' }"
 
 Object subclass:#PPToken
-	instanceVariableNames:'collection start stop'
-	classVariableNames:''
+	instanceVariableNames:'collection start stop value'
+	classVariableNames:'NewLineParser'
 	poolDictionaries:''
 	category:'PetitParser-Core'
 !
 
 
+!PPToken class methodsFor:'initialization'!
+
+initialize
+    "Platform independent newline sequence. LF: Unix, CR+LF: Windows, and CR: Apple."
+
+    |cr|
+
+    cr := Smalltalk isSmalltalkX 
+            ifTrue:[Character return] 
+            ifFalse:[Character cr].
+    NewLineParser := (Character lf asParser) / (cr asParser , Character lf asParser optional)
+! !
+
 !PPToken class methodsFor:'instance creation'!
 
 new
@@ -15,13 +28,20 @@
 !
 
 on: aSequenceableCollection
-	^ self on: aSequenceableCollection start: 1 stop: aSequenceableCollection size
+	^ self on: aSequenceableCollection start: 1 stop: aSequenceableCollection size value: nil
 !
 
 on: aSequenceableCollection start: aStartInteger stop: aStopInteger
 	^ self basicNew 
 		initializeOn: aSequenceableCollection
 		start: aStartInteger stop: aStopInteger
+!
+
+on: aSequenceableCollection start: aStartInteger stop: aStopInteger value: anObject
+	^ self basicNew 
+		initializeOn: aSequenceableCollection
+		start: aStartInteger stop: aStopInteger
+		value: anObject
 ! !
 
 !PPToken methodsFor:'accessing'!
@@ -33,7 +53,7 @@
 !
 
 size
-	"Answer the size of this token."
+	"Answer the size of this token in the underlying collection."
 
 	^ stop - start + 1
 !
@@ -48,28 +68,41 @@
 	"Answer the stop position of this token in the underlying collection."
 	
 	^ stop
+! !
+
+!PPToken methodsFor:'accessing-values'!
+
+inputValue
+	"Answer the consumed input of this token."
+
+	^ collection copyFrom: start to: stop
+!
+
+parsedValue
+	"Answer the parsed value of this token."
+
+	^ value
 !
 
 value
-	"Answer the contents of this token."
-
-	^ collection copyFrom: start to: stop
+	self notify: 'Token>>#value is no longer supported. Instead use Token>>#inputValue or the more pragmatic #parsedValue.'.
+	^ self inputValue
 ! !
 
 !PPToken methodsFor:'comparing'!
 
 = anObject
-	^ self class = anObject class and: [ self value = anObject value ]
+	^ self class = anObject class and: [ self parsedValue = anObject parsedValue ]
 !
 
 hash
-	^ self value hash
+	^ self parsedValue hash
 ! !
 
 !PPToken methodsFor:'copying'!
 
 copyFrom: aStartInteger to: aStopInteger
-	^ self class on: collection start: start + aStartInteger - 1 stop: stop + aStopInteger - 3
+	^ self class on: collection start: start + aStartInteger - 1 stop: stop + aStopInteger - 3 value: value
 ! !
 
 !PPToken methodsFor:'initialization'!
@@ -78,13 +111,21 @@
 	collection := aSequenceableCollection.
 	start := aStartInteger.
 	stop := aStopInteger
+!
+
+initializeOn: aSequenceableCollection start: aStartInteger stop: aStopInteger value: anObject
+	collection := aSequenceableCollection.
+	start := aStartInteger.
+	stop := aStopInteger.
+	value := anObject
 ! !
 
 !PPToken methodsFor:'printing'!
 
 printOn: aStream
 	super printOn: aStream.
-	aStream nextPut: $(; nextPutAll: self value; nextPut: $)
+	aStream nextPut: $[; print: self start; nextPut: $,; print: self stop; nextPut: $].
+	aStream nextPut: $(; print: self parsedValue; nextPut: $)
 ! !
 
 !PPToken methodsFor:'private'!
@@ -108,7 +149,7 @@
 	
 	| position |
 	position := 0.
-	(self newline , [ :stream |
+	(NewLineParser , [ :stream |
 		start <= stream position
 			ifTrue: [ ^ start - position ].
 		position := stream position ] asParser
@@ -122,7 +163,7 @@
 	
 	| line |
 	line := 1.
-	(self newline , [ :stream |
+	(NewLineParser , [ :stream |
 		start <= stream position
 			ifTrue: [ ^ line ].
 		line := line + 1 ] asParser
@@ -134,13 +175,16 @@
 !PPToken class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.4 2012-12-01 14:27:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.5 2014-03-04 14:32:08 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.4 2012-12-01 14:27:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPToken.st,v 1.5 2014-03-04 14:32:08 cg Exp $'
 !
 
 version_SVN
-    ^ '§Id: PPToken.st 2 2010-12-17 18:44:23Z vranyj1 §'
+    ^ '$Id: PPToken.st,v 1.5 2014-03-04 14:32:08 cg Exp $'
 ! !
+
+
+PPToken initialize!