compiler/PPCConfiguration.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 17 Aug 2015 12:13:16 +0100
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 518 a6d8b93441b0
child 524 f6f68d32de73
permissions -rw-r--r--
Updated to PetitCompiler-JanKurs.160, PetitCompiler-Tests-JanKurs.112, PetitCompiler-Extras-Tests-JanKurs.25, PetitCompiler-Benchmarks-JanKurs.17 Name: PetitCompiler-JanKurs.160 Author: JanKurs Time: 17-08-2015, 09:52:26.291 AM UUID: 3b4bfc98-8098-4951-af83-a59e2585b121 Name: PetitCompiler-Tests-JanKurs.112 Author: JanKurs Time: 16-08-2015, 05:00:32.936 PM UUID: 85613d47-08f3-406f-9823-9cdab451e805 Name: PetitCompiler-Extras-Tests-JanKurs.25 Author: JanKurs Time: 16-08-2015, 05:00:10.328 PM UUID: 09731810-51a1-4151-8d3a-56b636fbd1f7 Name: PetitCompiler-Benchmarks-JanKurs.17 Author: JanKurs Time: 05-08-2015, 05:29:32.407 PM UUID: e544b5f1-bcf8-470b-93a6-d2363e4dfc8a

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

"{ NameSpace: Smalltalk }"

Object subclass:#PPCConfiguration
	instanceVariableNames:'arguments ir history'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Core'
!

!PPCConfiguration class methodsFor:'as yet unclassified'!

default
    ^ self universal
!

new
    ^ self basicNew
        initialize;
        yourself
!

tokenizing
    ^ PPCTokenizingConfiguration new
!

universal
    ^ PPCUniversalConfiguration new
! !

!PPCConfiguration methodsFor:'accessing'!

arguments
 				arguments isNil ifTrue: [ arguments := self defaultArguments ].
				^ arguments
!

arguments: args
    arguments := args
!

defaultArguments
 				^ PPCArguments default
!

input: whatever
    ir := whatever.
    self remember: #input.
!

ir
    ^ ir
!

ir: whatever
    ir := whatever
! !

!PPCConfiguration methodsFor:'caching'!

cacheFirstSet
    "Creates a PPCNodes from a PPParser"
    | firstSets |
    firstSets := ir firstSets.
    ir allNodesDo: [ :node |
        node firstSet: (firstSets at: node)
    ]
!

cacheFirstSetWithProductions
    "Creates a PPCNodes from a PPParser"
    | firstSets |
    firstSets := ir firstSetsSuchThat: [:e | e name isNil not ].
    ir allNodesDo: [ :node |
        node firstSetWithProductions: (firstSets at: node)
    ]
!

cacheFirstSetWithTokens
    "Creates a PPCNodes from a PPParser"
    | firstSets |
    firstSets := ir firstSetsSuchThat: [:e | e isTerminal or: [ e isTokenNode ] ].
    ir allNodesDo: [ :node |
        node firstSetWithTokens: (firstSets at: node)
    ]
!

cacheFollowSet
    "Creates a PPCNodes from a PPParser"
    | followSets |
    followSets := ir followSets.
    ir allNodesDo: [ :node |
        node followSet: (followSets at: node)
    ]
!

cacheFollowSetWithTokens
    "Creates a PPCNodes from a PPParser"
    | followSets |
    followSets := ir followSetsSuchThat: [:e | e isTerminal or: [ e isTokenNode ] ].
    ir allNodesDo: [ :node |
        node followSetWithTokens: (followSets at: node)
    ]
! !

!PPCConfiguration methodsFor:'compiling'!

buildClass: compiler
    self subclassResponsibility
!

compile: whatever
    | time |
    self input: whatever.
    
    time := [ self invokePhases ] timeToRun asMilliSeconds.
    self reportTime: time.
    
    ^ ir
!

invokePhases
    self subclassResponsibility
! !

!PPCConfiguration methodsFor:'debugging'!

copy: somethingTransformable
    ^ somethingTransformable transform: [ :e | e copy ]
!

remember: key
    self arguments debug ifTrue: [ 
        history add: key -> (self copy: ir).
    ]
! !

!PPCConfiguration methodsFor:'hooks'!

codeCompiler
    ^ PPCCodeGen on: arguments 
!

codeCompilerOn: args
    ^ PPCCodeGen on: args
!

codeGeneratorVisitorOn: compiler
    ^ arguments codeGenerator on: compiler
! !

!PPCConfiguration methodsFor:'initialization'!

initialize
    history := OrderedCollection new
! !

!PPCConfiguration methodsFor:'phases'!

cacheFirstFollow
    arguments cacheFirstFollow ifFalse: [ ^ self ] .
    
    self cacheFirstSet.
    self cacheFollowSet.
    self cacheFirstSetWithTokens.
    self cacheFollowSetWithTokens.
!

check
    ir checkTree 
!

createRecognizingComponents
    arguments recognizingComponents ifFalse: [ ^ self ] .
    
    ir :=  PPCRecognizerComponentDetector new
        arguments: arguments;
        visit: ir.
    self remember: #recognizingComponents
!

createTokens
    arguments detectTokens ifFalse: [ ^ self ] .
    
    ir :=  PPCTokenDetector new
        arguments: arguments;
        visit: ir.
    self remember: #createTokens
!

generate
    |  compiler rootMethod compiledParser |
    arguments generate ifFalse: [ ^ self ].
    
    compiler := self codeCompiler.
    
    rootMethod := (self codeGeneratorVisitorOn: compiler)
        arguments: arguments;
        visit: ir.
    
    compiledParser := self buildClass: compiler.
    compiledParser startSymbol: rootMethod methodName.
    compiledParser := compiledParser new.
    
    ir := compiledParser.
!

inline
    arguments inline ifFalse: [ ^ self ].
    
    ir := PPCInliningVisitor new
        arguments: arguments;
        visit: ir.
    self remember: #inline.
!

merge
    "Merge equivalent nodes under one object with single identity"
    arguments merge ifFalse: [ ^ self ].
    
    ir :=  PPCMergingVisitor new
        arguments: arguments;
        visit: ir.
    self remember: #merge
!

specialize
    arguments specialize ifFalse: [ ^ self ].

    " 
        Invokes a visitor that creates specialized nodes
        for some patterns of PPCNodes, 
        
        e.g. $a astar can be represented by PPCCharacterStarNode
    "
    ir :=  (PPCSpecializingVisitor new
        arguments: arguments;
        visit: ir).
    self remember: #specialize
!

toPPCIr
    "Creates a PPCNodes from a PPParser"
    ir := ir asCompilerTree.
    self remember: #ppcNodes
! !

!PPCConfiguration methodsFor:'reporting'!

reportTime: timeInMs
    arguments profile ifTrue: [ 
        Transcript show: 'Time to compile: ', timeInMs asString, ' ms'; cr.
    ]
! !