parsers/smalltalk/PPSmalltalkTokenParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 23 Nov 2015 11:14:30 +0100
changeset 551 00ebb1b85f53
parent 417 3c0a91182e65
permissions -rw-r--r--
Fixed CI scripts on Windows For an unknown reason, unzip on Windows reports status code 50 (presumably "the disk is (or was) full during extraction.") even if there's plenty of space. To workaround this, simply ignore status code 50 on Windows. Sigh.

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