compiler/PPCTrimmingTokenNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 30 Jul 2015 08:37:37 +0100
changeset 510 869853decf31
parent 452 9f4558b3be66
child 515 b5316ef15274
permissions -rw-r--r--
Tests refactoring - use generated test cases to make sure all posibilities are tested. Do not generate resource for all combinations, use PPCSetUpBeforeTearDownAfterResource instead that delegates parser compilation to the testcase itself (it calls it's #setUpBefore method).

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

"{ NameSpace: Smalltalk }"

PPCListNode subclass:#PPCTrimmingTokenNode
	instanceVariableNames:'tokenClass'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Nodes'
!

!PPCTrimmingTokenNode methodsFor:'accessing'!

child
    
    ^ children at: 2
!

child: anObject
    
    children at: 2 put: anObject
!

prefix
    ^ #token
!

tokenClass
    
    ^ tokenClass
!

tokenClass: anObject
    
    tokenClass := anObject
!

whitespace
    
    ^ children at: 1
!

whitespace: anObject
    (anObject name isNil and: [ self child name isNotNil ]) ifTrue: [ 
        anObject name: self child name, '_ws'.
    ].
    children at: 1 put: anObject
! !

!PPCTrimmingTokenNode methodsFor:'analyzing'!

acceptsEpsilon
    ^ self child acceptsEpsilonOpenSet: (IdentitySet with: self).
!

acceptsEpsilonOpenSet: set
    (set includes: self child) ifFalse: [ 
        set add: self child.
        ^ self child acceptsEpsilonOpenSet: set 
    ].
    ^ false
!

firstSetSuchThat: block into: aCollection openSet: aSet
    (aSet includes: self) ifTrue: [ ^ aCollection ].
    aSet add: self.
    
    (block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
    
    ^ self child firstSetSuchThat: block into: aCollection openSet: aSet.
!

firstSets: aFirstDictionary into: aSet suchThat: aBlock
    "PRIVATE: Try to add additional elements to the first-set aSet of the receiver, use the incomplete aFirstDictionary."

    (aBlock value: self) ifFalse: [ 
        aSet addAll: (aFirstDictionary at: self child)
    ]
!

recognizedSentencesPrim
    ^ self child recognizedSentencesPrim 
! !

!PPCTrimmingTokenNode methodsFor:'comparing'!

= anotherNode
    super = anotherNode ifFalse: [ ^ false ].
    ^ tokenClass = anotherNode tokenClass.
!

hash
    ^ super hash bitXor: tokenClass hash
! !

!PPCTrimmingTokenNode methodsFor:'initialization'!

initialize
    super initialize.
    children := Array new: 2
! !

!PPCTrimmingTokenNode methodsFor:'testing'!

isTokenNode
    ^ true
!

isTrimmingTokenNode
    ^ true
! !

!PPCTrimmingTokenNode methodsFor:'visiting'!

accept: visitor
    ^ visitor visitTrimmingTokenNode: self
! !