parsers/smalltalk/PPSmalltalkTokenParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 16 Jun 2015 07:49:21 +0100
changeset 491 82b272c7dc37
parent 417 3c0a91182e65
permissions -rw-r--r--
Codegen: added support for smart action node compiling. Avoid creation of intermediate result collection for action nodes if all references to action block's argument (i.e., the nodes collection) is in form of: * <nodes> at: <numeric constant> * <nodes> first (second, third...

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