compiler/PPCTokenizingConfiguration.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 25 Aug 2015 01:30:32 +0100
changeset 530 e36906742693
parent 529 439c4057517f
child 531 dc3d13c2837d
permissions -rw-r--r--
PPCConfiguration refactoring: [2/10]: introduced PPCCompilationContext Moved parser class/scanner class instvars from PPCConfiguration subclasses to the context. Made PPCConfiguration to keep an instance of context. This is a preparation for having only one PPCConfiguration-like class.

"{ 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.
!

options: args
    super options: args.
! !

!PPCTokenizingConfiguration methodsFor:'phases'!

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

    "Modified: / 25-08-2015 / 00:07:38 / 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: options;
        yourself.
        
    fsas do: [ :fsa | generator generate: fsa ].

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

buildScannerTokens
    | generator  |
    generator :=  PPCTokenCodeGenerator new
        clazz: context scannerClass;
        options: options;
        yourself.

    generator visit: ir.

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

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: options;
        visit: ir.
        
    self remember: (self copyTree: ir) as: #LL1
!

generateParser
    | parserClass rootMethod |
    options generate ifFalse: [ ^ self ].
    rootMethod := context parserClass propertyAt: #rootMethod.
    
    context parserClass name: options parserName.
    context parserClass superclass: 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 <jan.vrany@fit.cvut.cz>"
!

generateScanner
    | scanner |
    options generate ifFalse: [ ^ self ].
    
    context scannerClass name: options scannerName.
    context scannerClass superclass: 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 <jan.vrany@fit.cvut.cz>"
!

tokenize
    "
        This will try transform the parser into the tokenizing parser
    "
    options tokenize ifFalse: [ ^ self ] .
    
    ir :=  PPCTokenizingVisitor new
        options: 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
        ]
    ]
! !

!PPCTokenizingConfiguration class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !