ParseNodeValidator.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 28 Jul 2011 16:57:44 +0200
changeset 2617 160ca364f3d3
parent 2611 42a3145f3ff5
child 2622 3a766e3136fa
permissions -rw-r--r--
More fixes for start/end position

"{ Package: 'stx:libcomp' }"

ParseNodeVisitor subclass:#ParseNodeValidator
	instanceVariableNames:'stack source'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler-Support'
!

!ParseNodeValidator class methodsFor:'documentation'!

documentation
"
    A helper class used to validate parse tree, i.e. parent instvar,
    startPosition/endPositions. Useful only for Parser debugging/hacking.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!ParseNodeValidator class methodsFor:'validation'!

validate: aParseNode source: source

    ^self basicNew validate: aParseNode source: source

    "Created: / 27-07-2011 / 13:43:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

validateImage

    self validateImage: false.

    "Created: / 20-07-2011 / 20:41:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

validateImage: stopOnError

    Smalltalk allClassesDo:[:cls|
        cls isLoaded ifTrue:[
            Transcript nextPut:$..
            cls methodsDo:[:mth|
                [ 
                    | src |
                    src := mth source.
                    self validate: (Parser parseMethod: src) tree source: src.
                ] on: Error do:[:ex|
                    Transcript 
                        cr;
                        show: mth printString;
                        show: '...FAILED!!';
                        cr.                        
                    stopOnError ifTrue:[
                        ex pass
                    ].
                ]                
            ].
        ].
    ].

    "Created: / 20-07-2011 / 20:42:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ParseNodeValidator methodsFor:'validation'!

validate: tree source: src

    tree isNil ifTrue:[^self].

    source := src.
    stack := Stack with: nil.

    ^self visit: tree

    "Created: / 27-07-2011 / 13:43:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

validateNode:node 

    self assert: node startPosition isInteger.
    self assert: node endPosition isInteger.
    self assert: node parent == stack top

    "Modified: / 27-07-2011 / 13:47:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ParseNodeValidator methodsFor:'visiting'!

visit:anObject 
    |accept stmt|

    accept := 
            [:node | 
            stack push:node.
            node acceptVisitor:self.
            stack pop.
            self validateNode:node. ].
    ^ anObject isStatementNode 
        ifTrue:
            [ stmt := anObject.
            [ stmt isNil ] whileFalse:
                    [ accept value:stmt.
                    stmt := stmt nextStatement. ] ]
        ifFalse:[ accept value:anObject. ]

    "Created: / 25-07-2011 / 23:14:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ParseNodeValidator class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/ParseNodeValidator.st,v 1.4 2011-07-27 15:01:34 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libcomp/ParseNodeValidator.st,v 1.4 2011-07-27 15:01:34 vrany Exp $'
! !