parsers/smalltalk/PPSmalltalkTokenParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 07 Oct 2014 09:42:03 +0100
changeset 385 44a36ed4e484
child 417 3c0a91182e65
permissions -rw-r--r--
Commited a Smalltalk parser (MC package PetitSmalltalk) Name: PetitSmalltalk-JanKurs.71 Author: JanKurs Time: 19-08-2014, 02:18:05 AM UUID: d1d11836-f3e2-4709-abd3-e2ff3b72d7c4 Repository: http://smalltalkhub.com/mc/Moose/PetitParser/main Ancestors: Fixes to be compatible with PPContext

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

PPTokenParser subclass:#PPSmalltalkTokenParser
	instanceVariableNames:''
	classVariableNames:'SeparatorPredicate'
	poolDictionaries:''
	category:'PetitSmalltalk-Core'
!

PPSmalltalkTokenParser comment:'A parser that knows how to skip comments and whitespace in Smalltalk and how to instantiate tokens.'
!


!PPSmalltalkTokenParser class methodsFor:'initialization'!

initialize
	SeparatorPredicate := PPCharSetPredicate on: [ :char | char isSeparator ]
! !

!PPSmalltalkTokenParser methodsFor:'parsing'!

parseComments: anArray on: aPPContext
	| start comments |
	comments := anArray.
	[ [ aPPContext atEnd not and: [ SeparatorPredicate value: aPPContext uncheckedPeek ] ]
		whileTrue: [ aPPContext next ].
	 aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
		aPPContext next.
		start := aPPContext position.
		aPPContext upTo: $".
		comments := comments copyWith: (start to: aPPContext position) ].
	^ comments
!

parseOn: aPPContext
	| memento comments token |
	memento := aPPContext remember.
	comments := self
		parseComments: #()
		on: aPPContext.
	token := super parseOn: aPPContext.
	token isPetitFailure ifTrue: [
		aPPContext restore: memento.
		^ token ].
	comments := self
		parseComments: comments
		on: aPPContext.
	^ token comments: comments
! !

!PPSmalltalkTokenParser methodsFor:'private'!

defaultTokenClass
	^ PPSmalltalkToken
! !

!PPSmalltalkTokenParser class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !


PPSmalltalkTokenParser initialize!