compiler/PPCAbstractPredicateNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 05 Nov 2014 23:05:19 +0000
changeset 414 0eaf09920532
parent 393 00381102a9b5
child 421 7e08b31e0dae
permissions -rw-r--r--
Merged JK's work on PetitCompiler Name: PetitCompiler-JanKurs.57 Author: JanKurs Time: 05-11-2014, 05:10:47 AM UUID: 4c625efe-77fd-465d-bd63-72ead0b5d3ba Name: PetitCompiler-Tests-JanVrany.13 Author: JanVrany Time: 05-11-2014, 09:31:07 AM UUID: 189ae287-6bc1-40ba-8458-b8392c4260a0

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

PPCNode subclass:#PPCAbstractPredicateNode
	instanceVariableNames:'predicate methodStrategy'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Nodes'
!

!PPCAbstractPredicateNode class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!PPCAbstractPredicateNode methodsFor:'accessing'!

methodStrategy
	
	^ methodStrategy
!

methodStrategy: anObject
	
	methodStrategy := anObject
!

predicate
	
	^ predicate
!

predicate: anObject
	
	predicate := anObject
!

prefix
	^ #predicate
! !

!PPCAbstractPredicateNode methodsFor:'analysis'!

= anotherNode
	(self == anotherNode) ifTrue: [ ^ true ].
	(anotherNode class = self class) ifFalse: [ ^ false ].
	
	(anotherNode name = name) ifFalse: [ ^ false ].
	(anotherNode methodStrategy = methodStrategy) ifFalse: [ ^ false ].
	^ anotherNode children = self children.
!

acceptsEpsilon
	^ false
!

firstCharParser
	^ PPPredicateObjectParser on: predicate message: 'predicate expected'.
!

firstCharSet
	^ PPCharSetPredicate on: predicate
! !

!PPCAbstractPredicateNode methodsFor:'compiling'!

bodyOfPredicate: compiler
	self subclassResponsibility
!

compileWith: compiler effect: effect id: id
	compiler startMethod: id.
	compiler add: '^'.
	self bodyOfPredicate: compiler.
 ^ compiler stopMethod.
!

extendClassification: classification
	^ (classification asOrderedCollection addLast: false; yourself) asArray
! !

!PPCAbstractPredicateNode methodsFor:'initialization'!

initialize
	super initialize.
	methodStrategy := PPCMethodStrategy new
! !

!PPCAbstractPredicateNode methodsFor:'optimizing'!

asInlined
	^ super asInlined
"	(methodStrategy == (PPCInlineStrategy instance)) ifFalse: [ 
		^ self copy 
			methodStrategy: PPCInlineStrategy instance;
			yourself
	].
	^ self"
!

optimize: params status: changeStatus
	| retval |
	retval := self.
	retval := retval rewrite: params status: changeStatus.
	retval := retval inline: params status: changeStatus.
	
	^ retval
! !