compiler/PPCTokenizingConfiguration.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 26 Aug 2015 21:41:20 +0100
changeset 531 dc3d13c2837d
parent 530 e36906742693
child 532 132d7898a2a1
permissions -rw-r--r--
PPCConfiguration refactoring: [3/10]: Moved some sime instvars to context Move some context-related options from PPCConfiguration to PPCCompilationContext. PPCConfiguration now access them wia accessor methods.

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

"{ NameSpace: Smalltalk }"

PPCConfiguration subclass:#PPCTokenizingConfiguration
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Core'
!

!PPCTokenizingConfiguration methodsFor:'compiling'!

buildClass: clazz
    |  builder |
    builder := PPCClassBuilder new.
    
    builder compiledClassName: clazz name.
    builder compiledSuperclass: clazz superclass.
    builder methodDictionary: clazz methodDictionary.
    builder constants: clazz constants.

    ^ builder compileClass.	
!

invokePhases
    self toPPCIr.
    self createTokens.
    self cacheFirstFollow.
    self createLL1Choices.
    self tokenize.
    self merge.
    self specialize.
    self createRecognizingComponents.
    self specialize.
    self inline.
    self merge.
    self check.	
    self cacheFirstFollow.
    self buildParserClazz.
    self unmarkConsumeTokensForInline.
    self createFSAs.
    self buildScannerTokens.
    self buildScannerScans.	
    self generateScanner.
    self generateParser.
! !

!PPCTokenizingConfiguration methodsFor:'error handling'!

buildParserClazz
    | rootMethod |

    rootMethod := (PPCTokenizingCodeGenerator new)
            clazz:context parserClass;
            options:context options;
            visit:ir.
    context parserClass propertyAt:#rootMethod put:rootMethod

    "Modified: / 25-08-2015 / 00:07:38 / Jan Vrany <jan.vrany@fit."
    "Modified: / 26-08-2015 / 19:57:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buildScannerScans
    | fsas  generator |

    "TODO JK: Perhpas write separate visitor for this?"
    fsas := IdentitySet new.
    fsas addAll:(ir allNodes 
                select:[:node | node hasFsa ]
                thenCollect:[:node | node fsa ]).
    fsas addAll:(ir allNodes 
                select:[:node | node hasNextFsa ]
                thenCollect:[:node | node nextFsa ]).
    fsas := fsas reject:[:fsa | fsa hasDistinctRetvals not ].
    generator := (PPCScannerCodeGenerator new)
            clazz:context scannerClass;
            options:context options;
            yourself.
    fsas do:[:fsa | 
        generator generate:fsa
    ].

    "Modified: / 25-08-2015 / 00:04:43 / Jan Vrany <jan.vrany@fit."
    "Modified: / 26-08-2015 / 19:57:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buildScannerTokens
    | generator |

    generator := (PPCTokenCodeGenerator new)
            clazz:context scannerClass;
            options:context options;
            yourself.
    generator visit:ir.

    "Modified: / 25-08-2015 / 00:04:46 / Jan Vrany <jan.vrany@fit."
    "Modified: / 26-08-2015 / 19:57:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateParser
    | parserClass  rootMethod |

    context options generate ifFalse:[
        ^ self
    ].
    rootMethod := context parserClass propertyAt:#rootMethod.
    context parserClass name:context options parserName.
    context parserClass superclass:context options parserSuperclass.
    parserClass := self buildClass:context parserClass.
    parserClass startSymbol:rootMethod methodName.
    self remember:parserClass as:#parser.
    ir := parserClass new

    "Modified: / 25-08-2015 / 00:05:49 / Jan Vrany"
    "Modified: / 26-08-2015 / 19:57:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

generateScanner
    | scanner |

    context options generate ifFalse:[
        ^ self
    ].
    context scannerClass name:context options scannerName.
    context scannerClass superclass:context options scannerSuperclass.
    scanner := (self buildClass:context scannerClass).
    context parserClass addConstant:scanner as:#scannerClass.
    ir := scanner.
    self remember:scanner as:#scanner

    "Modified: / 25-08-2015 / 00:06:49 / Jan Vrany"
    "Modified: / 26-08-2015 / 19:58:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCTokenizingConfiguration methodsFor:'phases'!

createFSAs
    ir := PPCFSAVisitor new
        idGen: context scannerClass idGen;
        visit: ir.

    self remember: (self copyTree: ir) as: #withFSAs

    "Modified: / 25-08-2015 / 00:07:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

createLL1Choices
    self flag:'This phase needs revisit and update'.
    ir := (PPCLL1Visitor new)
            options:context options;
            visit:ir.
    self remember:(self copyTree:ir) as:#LL1
!

tokenize
    "
        This will try transform the parser into the tokenizing parser"
    
    context options tokenize ifFalse:[
        ^ self
    ].
    ir := (PPCTokenizingVisitor new)
            options:context options;
            visit:ir.
    self remember:(self copyTree:ir) as:#tokenize
!

unmarkConsumeTokensForInline
    "TODO JK: Hack alert, use visitor, or at leas isTokenConsume"
    ir allNodesDo: [ :node |
        node class == PPCTokenConsumeNode ifTrue: [ 
            node unmarkForInline
        ]
    ]
! !