compiler/PPCompiledParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 24 Nov 2014 00:09:23 +0000
changeset 421 7e08b31e0dae
parent 392 9b297f0d949c
child 422 116d2b2af905
permissions -rw-r--r--
Merged JK's version from Monticello Name: PetitParser-JanKurs.260 Author: JanKurs Time: 17-11-2014, 12:09:05.490 PM UUID: 07411cef-ef69-40db-9d93-d4018a9b34ef Name: PetitTests-JanKurs.65 Author: JanKurs Time: 17-11-2014, 12:09:04.530 PM UUID: f98d613f-f4ce-4e0e-a7e9-310ee7c7e7a6 Name: PetitSmalltalk-JanKurs.78 Author: JanKurs Time: 14-11-2014, 05:05:07.765 PM UUID: 3d68330d-44d5-46c3-9705-97f627b3edbc Name: PetitCompiler-JanKurs.71 Author: JanKurs Time: 18-11-2014, 09:48:35.425 AM UUID: 06352c33-3c76-4382-8536-0cc48e225117 Name: PetitCompiler-Tests-JanKurs.21 Author: JanKurs Time: 17-11-2014, 05:51:53.134 PM UUID: 8d6c0799-14e7-4871-8d91-8b0f9886db83 Name: PetitCompiler-Benchmarks-JanKurs.2 Author: JanKurs Time: 17-11-2014, 05:51:07.887 PM UUID: d5e3a980-7871-487a-a232-e3ca93fc2483

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

PPParser subclass:#PPCompiledParser
	instanceVariableNames:'startSymbol context failure error'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Core'
!

PPCompiledParser class instanceVariableNames:'parsers constants referringParser'

"
 No other class instance variables are inherited by this class.
"
!

!PPCompiledParser class methodsFor:'as yet unclassified'!

addConstant: value as: id
        self constants at: id ifPresent: [ :ignored | 
                ((self constants at: id) = value) ifFalse: [self error: 'ooups']].      
        
        self constants at: id put: value.

    "Modified: / 21-11-2014 / 12:32:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addParser: aPPParser as: id
	
	"(self parsers includesKey: id) ifTrue: [self error: 'Ooups' ]."
	self parsers at: id put: aPPParser.
!

constants
	constants ifNil: [ constants := IdentityDictionary new ].
	^ constants
!

parse: input
	^ self new parse: input
!

parsers
	parsers ifNil: [ parsers := IdentityDictionary new ].
	^ parsers
!

referringParser
	^ referringParser 
!

referringParser: aPPParser
	referringParser := aPPParser
! !

!PPCompiledParser methodsFor:'as yet unclassified'!

callParser: id
	| retval |
	retval := (self class parsers at: id) parseOn: context.
	retval isPetitFailure 	ifTrue: [ self error: retval message at: retval position ]
									ifFalse: [ self clearError ].
	^ retval
!

clearError
	error := false.
!

error
	^ self error: '' at: context position
!

error: message
	^ self error: message at: context position
!

error: aMessage at: position
	failure position < position ifTrue: [
		failure message: aMessage.
		failure position: position
	].
	error := true.
	^ failure
!

initialize
	super initialize.
	
	self class constants keysAndValuesDo: [ :key :value |
		self instVarNamed: key put: value.
	].

	startSymbol := #start.

	

!

isCompiled
	^ true
!

isError
	^ error
!

parse: input rule: symbol
	startSymbol := symbol.
	^ self parse: input.
!

start
	^ self subclassResponsibility
!

startSymbol: aSymbol
	startSymbol := aSymbol
!

updateContext: aPPContext
	self class referringParser allParsersDo: [ :p | p updateContext: aPPContext ].
! !

!PPCompiledParser methodsFor:'parsing'!

parseOn: aPPContext
	| retval |
"	context := aPPContext asCompiledParserContext."
	context := aPPContext.
	context compiledParser: self.
	failure := PPFailure new message: nil; context: context; position: -1.
	context noteFailure: failure.
	error := false.

	retval := self perform: startSymbol.
	(retval isPetitFailure) ifTrue: [ aPPContext noteFailure: failure ].
	error ifTrue: [ aPPContext noteFailure: failure. retval := failure ].
	
"	aPPContext position: context position."
	^ retval
! !