compiler/benchmarks/PPCBenchmark.st
changeset 538 16e8536f5cfb
parent 537 fb212e14d1f4
equal deleted inserted replaced
537:fb212e14d1f4 538:16e8536f5cfb
     1 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
     1 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 Object subclass:#PPCBenchmark
     5 Object subclass:#PPCBenchmark
     6 	instanceVariableNames:'sources report contextClass compile parser context input
     6 	instanceVariableNames:'sources report contextClass compile parser context input compiler
     7 		compiler profile repetitions'
     7 		profile repetitions'
     8 	classVariableNames:''
     8 	classVariableNames:''
     9 	poolDictionaries:''
     9 	poolDictionaries:''
    10 	category:'PetitCompiler-Benchmarks-Core'
    10 	category:'PetitCompiler-Benchmarks-Core'
    11 !
    11 !
    12 
    12 
   321 !
   321 !
   322 
   322 
   323 benchmarkSmalltalkParserCompiled
   323 benchmarkSmalltalkParserCompiled
   324     | time |
   324     | time |
   325 
   325 
   326     compiler := PPCCompiler default.
   326     compiler := PPCCompiler new.
   327     parser := PPSmalltalkParser new compileUsingCompiler:compiler.
   327     parser := compiler compile: (PPSmalltalkParser new).
   328     context := PPCContext new.
   328     context := PPCContext new.
   329     context initializeFor:parser.
   329     context initializeFor:parser.
   330     input := sources smalltalkSourcesBig.
   330     input := sources smalltalkSourcesBig.
   331     time := [
   331     time := [
   332             input do:[:source | 
   332             input do:[:source | 
   336             asMilliSeconds.
   336             asMilliSeconds.
   337     self 
   337     self 
   338         reportInput:input
   338         reportInput:input
   339         time:time
   339         time:time
   340         name:'Smalltalk Parser Compiled'.
   340         name:'Smalltalk Parser Compiled'.
       
   341 
       
   342     "Modified: / 07-09-2015 / 11:38:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   341 ! !
   343 ! !
   342 
   344 
   343 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   345 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   344 
   346 
   345 benchmarkExpressionGrammarC
   347 benchmarkExpressionGrammarC
   551     context initializeFor: parser.
   553     context initializeFor: parser.
   552     input := sources expressionSourcesMedium.
   554     input := sources expressionSourcesMedium.
   553 !
   555 !
   554 
   556 
   555 setupExpressionGrammarCompiled
   557 setupExpressionGrammarCompiled
   556     compiler := PPCCompiler universal.
   558     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   557     compiler options parserName:#PPCompiledExpressionGrammar.
   559     compiler options parserName:#PPCompiledExpressionGrammar.
   558     compiler options scannerName:#PPCompiledExpressionScanner.
   560     compiler options scannerName:#PPCompiledExpressionScanner.
   559     parser := PPExpressionGrammar new compileUsingCompiler:compiler.
   561     parser := compiler compile: (PPExpressionGrammar new).
   560     context := self context.
   562     context := self context.
   561     context initializeFor:parser.
   563     context initializeFor:parser.
   562     input := sources expressionSourcesMedium.
   564     input := sources expressionSourcesMedium.
       
   565 
       
   566     "Modified: / 07-09-2015 / 11:38:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   563 !
   567 !
   564 
   568 
   565 setupExpressionGrammarTokenized
   569 setupExpressionGrammarTokenized
   566     compiler := PPCCompiler tokenizing.
   570     compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
   567     compiler options parserName:#PPTokenizedExpressionGrammar.
   571     compiler options parserName:#PPTokenizedExpressionGrammar.
   568     compiler options scannerName:#PPTokenizedExpressionScanner.
   572     compiler options scannerName:#PPTokenizedExpressionScanner.
   569     parser := PPExpressionGrammar new compileUsingCompiler:compiler.
   573     parser := compiler compile: (PPExpressionGrammar new).
   570     context := self context.
   574     context := self context.
   571     context initializeFor:parser.
   575     context initializeFor:parser.
   572     input := sources expressionSourcesMedium.
   576     input := sources expressionSourcesMedium.
       
   577 
       
   578     "Modified: / 07-09-2015 / 11:36:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   573 !
   579 !
   574 
   580 
   575 setupJavaSyntax
   581 setupJavaSyntax
   576     
   582     
   577     parser := PPJavaSyntax new.
   583     parser := PPJavaSyntax new.
   600     context initializeFor: parser.
   606     context initializeFor: parser.
   601     input := sources expressionSourcesBig.
   607     input := sources expressionSourcesBig.
   602 !
   608 !
   603 
   609 
   604 setupLL1ExpressionGrammarCompiled
   610 setupLL1ExpressionGrammarCompiled
   605     compiler := PPCCompiler universal.
   611     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   606     compiler options parserName:#PPCompiledLL1ExpressionGrammar.
   612     compiler options parserName:#PPCompiledLL1ExpressionGrammar.
   607     compiler options scannerName:#PPCompiledLL1ExpressionScanner.
   613     compiler options scannerName:#PPCompiledLL1ExpressionScanner.
   608     parser := PPLL1ExpressionGrammar new compileUsingCompiler:compiler.
   614     parser := compiler compile: (PPLL1ExpressionGrammar new).
   609     context := self context.
   615     context := self context.
   610     context initializeFor:parser.
   616     context initializeFor:parser.
   611     input := sources expressionSourcesBig.
   617     input := sources expressionSourcesBig.
       
   618 
       
   619     "Modified: / 07-09-2015 / 11:37:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   612 !
   620 !
   613 
   621 
   614 setupLL1ExpressionGrammarTokenized
   622 setupLL1ExpressionGrammarTokenized
   615     compiler := PPCCompiler tokenizing.
   623     compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
   616     compiler options parserName:#PPTokenizedLL1ExpressionGrammar.
   624     compiler options parserName:#PPTokenizedLL1ExpressionGrammar.
   617     compiler options scannerName:#PPTokenizedLL1ExpressionScanner.
   625     compiler options scannerName:#PPTokenizedLL1ExpressionScanner.
   618     parser := PPLL1ExpressionGrammar new compileUsingCompiler:compiler.
   626     parser := compiler compile: (PPLL1ExpressionGrammar new).
   619     context := self context.
   627     context := self context.
   620     context initializeFor:parser.
   628     context initializeFor:parser.
   621     input := sources expressionSourcesBig.
   629     input := sources expressionSourcesBig.
       
   630 
       
   631     "Modified: / 07-09-2015 / 11:36:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   622 !
   632 !
   623 
   633 
   624 setupLRPParser
   634 setupLRPParser
   625     
   635     
   626     parser := PPCLRPParser new.
   636     parser := PPCLRPParser new.
   630 
   640 
   631     "Created: / 18-08-2015 / 16:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   641     "Created: / 18-08-2015 / 16:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   632 !
   642 !
   633 
   643 
   634 setupLRPParserCompiled
   644 setupLRPParserCompiled
   635     compiler := PPCCompiler universal.
   645     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   636     parser := PPCLRPParser new compileUsingCompiler:compiler.
   646     parser := compiler compile: (PPCLRPParser new).
   637     context := self context.
   647     context := self context.
   638     context initializeFor:parser.
   648     context initializeFor:parser.
   639     input := PPCLRPSourcesResource current sources
   649     input := PPCLRPSourcesResource current sources
   640 
   650 
   641     "Created: / 18-08-2015 / 16:35:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   651     "Created: / 18-08-2015 / 16:35:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   652     "Modified: / 07-09-2015 / 11:37:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   642 !
   653 !
   643 
   654 
   644 setupLRPParser_johanfabry_39     
   655 setupLRPParser_johanfabry_39     
   645     
   656     
   646     parser := PPCLRPParser_johanfabry_39 new.
   657     parser := PPCLRPParser_johanfabry_39 new.
   663     context initializeFor: parser.
   674     context initializeFor: parser.
   664     input := sources smalltalkSourcesBig.
   675     input := sources smalltalkSourcesBig.
   665 !
   676 !
   666 
   677 
   667 setupSmalltalkGrammarCompiled
   678 setupSmalltalkGrammarCompiled
   668     compiler := PPCCompiler universal.
   679     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   669     compiler options parserName:#'PPSmalltalkGrammarC_Unviersal'.
   680     compiler options parserName:#'PPSmalltalkGrammarC_Unviersal'.
   670     compiler options profile:profile.
   681     compiler options profile:profile.
   671     parser := PPSmalltalkGrammar new compileUsingCompiler:compiler.
   682     parser := compiler compile: (PPSmalltalkGrammar new).
   672     context := self context.
   683     context := self context.
   673     context initializeFor:parser.
   684     context initializeFor:parser.
   674     profile ifTrue:[
   685     profile ifTrue:[
   675         input := sources smalltalkSourcesSmall.
   686         input := sources smalltalkSourcesSmall.
   676     ] ifFalse:[
   687     ] ifFalse:[
   677         input := sources smalltalkSourcesBig.
   688         input := sources smalltalkSourcesBig.
   678     ]
   689     ]
       
   690 
       
   691     "Modified: / 07-09-2015 / 11:37:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   679 !
   692 !
   680 
   693 
   681 setupSmalltalkGrammarTokenized
   694 setupSmalltalkGrammarTokenized
   682     compiler := PPCCompiler tokenizing.
   695     compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
   683     compiler options parserName:#'PPSmalltalkGrammarC_Tokenizing'.
   696     compiler options parserName:#'PPSmalltalkGrammarC_Tokenizing'.
   684     compiler options scannerName:#'PPSmalltalkGrammarC_Scanner'.
   697     compiler options scannerName:#'PPSmalltalkGrammarC_Scanner'.
   685     compiler options profile:profile.
   698     compiler options profile:profile.
   686     parser := PPSmalltalkGrammar new compileUsingCompiler:compiler.
   699     parser := compiler compile: (PPSmalltalkGrammar new).
   687     context := self context.
   700     context := self context.
   688     context initializeFor:parser.
   701     context initializeFor:parser.
   689     profile ifTrue:[
   702     profile ifTrue:[
   690         input := sources smalltalkSourcesSmall.
   703         input := sources smalltalkSourcesSmall.
   691     ] ifFalse:[
   704     ] ifFalse:[
   692         input := sources smalltalkSourcesBig.
   705         input := sources smalltalkSourcesBig.
   693     ]
   706     ]
       
   707 
       
   708     "Modified: / 07-09-2015 / 11:36:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   694 !
   709 !
   695 
   710 
   696 setupSmalltalkNoopParserCompiled
   711 setupSmalltalkNoopParserCompiled
   697     compiler := PPCCompiler universal.
   712     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   698     parser := PPCSmalltalkNoopParser new compileUsingCompiler:compiler.
   713     parser := compiler compile: (PPCSmalltalkNoopParser new).
   699     context := PPCContext new.
   714     context := PPCContext new.
   700     context initializeFor:parser.
   715     context initializeFor:parser.
   701     input := sources smalltalkSourcesBig.
   716     input := sources smalltalkSourcesBig.
   702 
   717 
   703     "Created: / 16-05-2015 / 09:44:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   718     "Created: / 16-05-2015 / 09:44:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   719     "Modified: / 07-09-2015 / 11:37:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   704 !
   720 !
   705 
   721 
   706 setupSmalltalkNoopParserTokenized
   722 setupSmalltalkNoopParserTokenized
   707     compiler := PPCCompiler tokenizing.
   723     compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
   708     parser := PPCSmalltalkNoopParser new compileUsingCompiler:compiler.
   724     parser := compiler compile: (PPCSmalltalkNoopParser new).
   709     context := PPCContext new.
   725     context := PPCContext new.
   710     context initializeFor:parser.
   726     context initializeFor:parser.
   711     input := sources smalltalkSourcesBig.
   727     input := sources smalltalkSourcesBig.
   712 
   728 
   713     "Created: / 16-05-2015 / 09:44:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   729     "Created: / 16-05-2015 / 09:44:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   730     "Modified: / 07-09-2015 / 11:36:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   714 !
   731 !
   715 
   732 
   716 setupSmalltalkParser
   733 setupSmalltalkParser
   717     
   734     
   718     parser := PPSmalltalkParser new.
   735     parser := PPSmalltalkParser new.
   720     context initializeFor: parser.
   737     context initializeFor: parser.
   721     input := sources smalltalkSourcesBig.
   738     input := sources smalltalkSourcesBig.
   722 !
   739 !
   723 
   740 
   724 setupSmalltalkParserCompiled
   741 setupSmalltalkParserCompiled
   725     compiler := PPCCompiler universal.
   742     compiler := PPCCompiler newWithOptions: #( #tokenize: false ).
   726     parser := PPSmalltalkParser new compileUsingCompiler:compiler.
   743     parser := compiler compile: (PPSmalltalkParser new).
   727     context := self context.
   744     context := self context.
   728     context initializeFor:parser.
   745     context initializeFor:parser.
   729     input := sources smalltalkSourcesBig.
   746     input := sources smalltalkSourcesBig.
       
   747 
       
   748     "Modified: / 07-09-2015 / 11:37:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   730 !
   749 !
   731 
   750 
   732 setupSmalltalkParserTokenized
   751 setupSmalltalkParserTokenized
   733     compiler := PPCCompiler tokenizing.
   752     compiler := PPCCompiler newWithOptions: #( #tokenize: true ).
   734     parser := PPSmalltalkParser new compileUsingCompiler:compiler.
   753     parser := compiler compile: (PPSmalltalkParser new).
   735     context := self context.
   754     context := self context.
   736     context initializeFor:parser.
   755     context initializeFor:parser.
   737     input := sources smalltalkSourcesBig.
   756     input := sources smalltalkSourcesBig.
       
   757 
       
   758     "Modified: / 07-09-2015 / 11:36:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   738 !
   759 !
   739 
   760 
   740 teardownExpressionGrammarTokenized
   761 teardownExpressionGrammarTokenized
   741     parser class removeFromSystem.
   762     parser class removeFromSystem.
   742 !
   763 !