compiler/PPCTokenizingConfiguration.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 17 Aug 2015 23:11:56 +0100
changeset 518 a6d8b93441b0
parent 516 3b81c9e53352
child 525 751532c8f3db
permissions -rw-r--r--
Portability fixes * do not use Object>>asString. Not all Smalltalks implement it. * do not use Object>>name. Not all Smalltalks implement it. * do not use Dictionary keysAndValuesRemove:. Not all Smalltalks implement it. * do not use Class>>methods The semantics is different among Smalltalks. Use `Class methodDictionary values` instead. * do not modify dictionary in #at:ifAbsentPut: block!

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

"{ NameSpace: Smalltalk }"

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


!PPCTokenizingConfiguration methodsFor:'compiling'!

buildClass: compiler
    |  builder |
    builder := PPCClassBuilder new.
    
    builder compiledClassName: arguments parserName.
    builder compiledSuperclass: PPTokenizingCompiledParser.
    builder methodDictionary: compiler methodDictionary.
    builder constants: compiler 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 generateScanner.		"Please note that codeGen is shared between these two phases"
    self generate.
! !

!PPCTokenizingConfiguration methodsFor:'hooks'!

codeCompiler
    codeGen isNil ifTrue: [ codeGen := PPCTokenizingCodeGen on: arguments ].
    ^ codeGen
!

codeCompilerOn: args
    ^ PPCTokenizingCompiler on: args
!

codeGeneratorVisitorOn: compiler
    ^ PPCTokenizingCodeGenerator on: compiler
! !

!PPCTokenizingConfiguration methodsFor:'phases'!

createLL1Choices
    ir :=  PPCLL1Visitor new
        arguments: arguments;
        visit: ir.
    self remember: #LL1
!

generateScanner
    | generator scanner |
    generator :=  PPCTokenCodeGenerator new
        compiler: self codeCompiler;
        arguments: arguments;
        yourself.

    generator visit: ir.
    
    scanner := generator compileScanner.	
    self codeCompiler addConstant: scanner as: #scannerClass.
!

tokenize
    "
        This will try transform the parser into the tokenizing parser
    "
    arguments tokenize ifFalse: [ ^ self ] .
    
    ir :=  PPCTokenizingVisitor new
        arguments: arguments;
        visit: ir.
    self remember: #tokenize
! !

!PPCTokenizingConfiguration class methodsFor:'documentation'!

version_HG

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