compiler/benchmarks/PPCBenchmark.st
changeset 465 f729f6cd3c76
parent 462 89464ab03518
parent 464 f6d77fee9811
child 503 ff58cd9f1f3c
equal deleted inserted replaced
463:d4014e0a47a0 465:f729f6cd3c76
     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
     7 		configuration'
     7 		configuration profile'
     8 	classVariableNames:''
     8 	classVariableNames:''
     9 	poolDictionaries:''
     9 	poolDictionaries:''
    10 	category:'PetitCompiler-Benchmarks-Core'
    10 	category:'PetitCompiler-Benchmarks-Core'
    11 !
    11 !
    12 
    12 
    69     compile := value
    69     compile := value
    70 !
    70 !
    71 
    71 
    72 measure: aParser on: anInput name: aString
    72 measure: aParser on: anInput name: aString
    73     | time result p |
    73     | time result p |
    74     context := self createContext.
    74     self halt: 'deprecated?'.
       
    75     context := self context.
    75     
    76     
    76     p := compile ifTrue: [ 
    77     p := compile ifTrue: [ 
    77         aParser end compile
    78         aParser end compile
    78     ] ifFalse: [ 
    79     ] ifFalse: [ 
    79         aParser end
    80         aParser end
   104     ((aContext rememberCount / input size) asFloat asString truncateTo: 6),
   105     ((aContext rememberCount / input size) asFloat asString truncateTo: 6),
   105     '.'.
   106     '.'.
   106 "
   107 "
   107 !
   108 !
   108 
   109 
   109 reportInput: input time: time name: name
   110 reportInput: anInput time: time name: name
   110     | size |
   111     | size |
   111     size := input inject: 0 into: [:r :e | r + e size  ].
   112     size := anInput inject: 0 into: [:r :e | r + e size  ].
   112     Transcript crShow: 'Size: ', size asString.
   113     Transcript crShow: 'Size: ', size asString.
   113     Transcript crShow: name, ' time: ', time asString.
   114     Transcript crShow: name, ' time: ', time asString.
   114     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   115     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   116     
       
   117     (context isKindOf: PPCProfilingContext) ifTrue: [ 
       
   118         context inspect.
       
   119     ]
   115 ! !
   120 ! !
   116 
   121 
   117 !PPCBenchmark methodsFor:'benchmarks'!
   122 !PPCBenchmark methodsFor:'benchmarks'!
   118 
   123 
   119 benchmarkJavaSyntax
   124 benchmarkJavaSyntax
   142     input := sources javaSourcesBig.
   147     input := sources javaSourcesBig.
   143 
   148 
   144     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   149     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   145     
   150     
   146     self reportInput: input time: time name: 'Java Syntax Compiled'.
   151     self reportInput: input time: time name: 'Java Syntax Compiled'.
   147 !
   152 ! !
       
   153 
       
   154 !PPCBenchmark methodsFor:'benchmarks - expression grammar'!
       
   155 
       
   156 benchmarkExpressionGrammar
       
   157     | time |
       
   158 
       
   159     self setupExpressionGrammar.
       
   160 
       
   161     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   162     
       
   163     self reportInput: input time: time name: 'Expression Grammar'.
       
   164 !
       
   165 
       
   166 benchmarkExpressionGrammarCompiled
       
   167     | time |
       
   168 
       
   169     self setupExpressionGrammarCompiled.
       
   170 
       
   171     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   172     
       
   173     self reportInput: input time: time name: 'Compiled Expression Grammar'.
       
   174 !
       
   175 
       
   176 benchmarkExpressionGrammarTokenized
       
   177     | time |
       
   178 
       
   179     self setupExpressionGrammarTokenized.
       
   180 
       
   181     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   182     
       
   183     self reportInput: input time: time name: 'Tokenized Expression Grammar'.
       
   184 !
       
   185 
       
   186 benchmarkLL1ExpressionGrammar
       
   187     | time |
       
   188 
       
   189     self setupLL1ExpressionGrammar.
       
   190 
       
   191     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   192     
       
   193     self reportInput: input time: time name: 'LL1 Expression Grammar'.
       
   194 !
       
   195 
       
   196 benchmarkLL1ExpressionGrammarCompiled
       
   197     | time |
       
   198 
       
   199     self setupLL1ExpressionGrammarCompiled.
       
   200 
       
   201     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   202     
       
   203     self reportInput: input time: time name: 'Compiled LL1 Expression Grammar'.
       
   204 !
       
   205 
       
   206 benchmarkLL1ExpressionGrammarTokenized
       
   207     | time |
       
   208 
       
   209     self setupLL1ExpressionGrammarTokenized.
       
   210 
       
   211     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   212     
       
   213     self reportInput: input time: time name: 'Tokenized LL1 Expression Grammar'.
       
   214 ! !
       
   215 
       
   216 !PPCBenchmark methodsFor:'benchmarks - micro'!
       
   217 
       
   218 benchmarkAnyStar
       
   219 "
       
   220     self measure: self anyStar on: sources petitParserPackage.
       
   221 "	
       
   222     self measure: self anyStar on: (sources changesSized: 1000*1000) name: #anyStar.
       
   223 !
       
   224 
       
   225 benchmarkAnyStarBlock
       
   226 "
       
   227     self measure: self anyStar on: sources petitParserPackage.
       
   228 "	
       
   229     self measure: self anyStarBlock on: (sources changesSized: 1000*1000) name: #anyStarBlock.
       
   230 !
       
   231 
       
   232 benchmarkToken
       
   233 "
       
   234     self measure: self anyStar on: sources petitParserPackage.
       
   235 "	
       
   236     parser := (self tokenParser / #any asParser) star.
       
   237     self measure: parser on: (sources changesSized: 1000*1000) name: #token.
       
   238 ! !
       
   239 
       
   240 !PPCBenchmark methodsFor:'benchmarks - smalltalk'!
   148 
   241 
   149 benchmarkOpalCompiler
   242 benchmarkOpalCompiler
   150     | parser time input |
   243     | parser time input |
   151     parser := OpalCompiler new.
   244     parser := OpalCompiler new.
   152     input := sources smalltalkSourcesBig.
   245     input := sources smalltalkSourcesBig.
   221     input := sources smalltalkSourcesBig.
   314     input := sources smalltalkSourcesBig.
   222 
   315 
   223     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   316     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   224     
   317     
   225         self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
   318         self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
   226 ! !
       
   227 
       
   228 !PPCBenchmark methodsFor:'benchmarks - expression grammar'!
       
   229 
       
   230 benchmarkExpressionGrammar
       
   231     | time |
       
   232 
       
   233     self setupExpressionGrammar.
       
   234 
       
   235     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   236     
       
   237     self reportInput: input time: time name: 'Expression Grammar'.
       
   238 !
       
   239 
       
   240 benchmarkExpressionGrammarCompiled
       
   241     | time |
       
   242 
       
   243     self setupExpressionGrammarCompiled.
       
   244 
       
   245     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   246     
       
   247     self reportInput: input time: time name: 'Compiled Expression Grammar'.
       
   248 !
       
   249 
       
   250 benchmarkExpressionGrammarTokenized
       
   251     | time |
       
   252 
       
   253     self setupExpressionGrammarTokenized.
       
   254 
       
   255     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   256     
       
   257     self reportInput: input time: time name: 'Tokenized Expression Grammar'.
       
   258 !
       
   259 
       
   260 benchmarkLL1ExpressionGrammar
       
   261     | time |
       
   262 
       
   263     self setupLL1ExpressionGrammar.
       
   264 
       
   265     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   266     
       
   267     self reportInput: input time: time name: 'LL1 Expression Grammar'.
       
   268 !
       
   269 
       
   270 benchmarkLL1ExpressionGrammarCompiled
       
   271     | time |
       
   272 
       
   273     self setupLL1ExpressionGrammarCompiled.
       
   274 
       
   275     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   276     
       
   277     self reportInput: input time: time name: 'Compiled LL1 Expression Grammar'.
       
   278 !
       
   279 
       
   280 benchmarkLL1ExpressionGrammarTokenized
       
   281     | time |
       
   282 
       
   283     self setupLL1ExpressionGrammarTokenized.
       
   284 
       
   285     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   286     
       
   287     self reportInput: input time: time name: 'Tokenized LL1 Expression Grammar'.
       
   288 ! !
       
   289 
       
   290 !PPCBenchmark methodsFor:'benchmarks - micro'!
       
   291 
       
   292 benchmarkAnyStar
       
   293 "
       
   294     self measure: self anyStar on: sources petitParserPackage.
       
   295 "	
       
   296     self measure: self anyStar on: (sources changesSized: 1000*1000) name: #anyStar.
       
   297 !
       
   298 
       
   299 benchmarkAnyStarBlock
       
   300 "
       
   301     self measure: self anyStar on: sources petitParserPackage.
       
   302 "	
       
   303     self measure: self anyStarBlock on: (sources changesSized: 1000*1000) name: #anyStarBlock.
       
   304 !
       
   305 
       
   306 benchmarkToken
       
   307 "
       
   308     self measure: self anyStar on: sources petitParserPackage.
       
   309 "	
       
   310     parser := (self tokenParser / #any asParser) star.
       
   311     self measure: parser on: (sources changesSized: 1000*1000) name: #token.
       
   312 ! !
   319 ! !
   313 
   320 
   314 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   321 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   315 
   322 
   316 benchmarkExpressionGrammarC
   323 benchmarkExpressionGrammarC
   423     "Created: / 16-05-2015 / 09:45:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   430     "Created: / 16-05-2015 / 09:45:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   424 ! !
   431 ! !
   425 
   432 
   426 !PPCBenchmark methodsFor:'intitialization'!
   433 !PPCBenchmark methodsFor:'intitialization'!
   427 
   434 
   428 createContext
   435 context
   429     ^ contextClass new
   436     ^ contextClass new
   430 !
   437 !
   431 
   438 
   432 initialize
   439 initialize
   433     super initialize.
   440     super initialize.
   434     sources := PPCResources current.
   441     sources := PPCResources current.
   435     contextClass := PPCContext.
   442     contextClass := PPCContext.
       
   443 
   436     compile := false.
   444     compile := false.
       
   445     profile := false.
   437 ! !
   446 ! !
   438 
   447 
   439 !PPCBenchmark methodsFor:'meta'!
   448 !PPCBenchmark methodsFor:'meta'!
   440 
   449 
   441 getMetaInfo: key
   450 getMetaInfo: key
   466 
   475 
   467 tokenParser
   476 tokenParser
   468     ^ #letter asParser, (#letter asParser / #digit asParser) star trim
   477     ^ #letter asParser, (#letter asParser / #digit asParser) star trim
   469 ! !
   478 ! !
   470 
   479 
       
   480 !PPCBenchmark methodsFor:'profiling'!
       
   481 
       
   482 profile
       
   483     contextClass := PPCProfilingContext.
       
   484     profile := true.
       
   485 ! !
       
   486 
   471 !PPCBenchmark methodsFor:'setup & teardown'!
   487 !PPCBenchmark methodsFor:'setup & teardown'!
   472 
   488 
   473 setupExpressionGrammar
   489 setupExpressionGrammar
   474     
   490     
   475     parser := PPExpressionGrammar new.
   491     parser := PPExpressionGrammar new.
   476     context := PPCContext new.
   492     context := self context.
   477     context initializeFor: parser.
   493     context initializeFor: parser.
   478     input := sources expressionSourcesMedium.
   494     input := sources expressionSourcesMedium.
   479 !
   495 !
   480 
   496 
   481 setupExpressionGrammarCompiled
   497 setupExpressionGrammarCompiled
   482     
   498     
   483     configuration := PPCConfiguration universal.
   499     configuration := PPCConfiguration universal.
   484     configuration arguments name: #PPCompiledExpressionGrammar.
   500     configuration arguments name: #PPCompiledExpressionGrammar.
   485     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   501     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   486     context := PPCContext new.
   502     context := self context.
   487     context initializeFor: parser.
   503     context initializeFor: parser.
   488     input := sources expressionSourcesMedium.
   504     input := sources expressionSourcesMedium.
   489 !
   505 !
   490 
   506 
   491 setupExpressionGrammarTokenized
   507 setupExpressionGrammarTokenized
   492     
   508     
   493     configuration := PPCConfiguration LL1.
   509     configuration := PPCConfiguration tokenizing.
   494     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   510     configuration arguments name: #PPTokenizedExpressionGrammar.
   495     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   511     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   496     context := PPCContext new.
   512     context := self context.
   497     context initializeFor: parser.
   513     context initializeFor: parser.
   498     input := sources expressionSourcesMedium.
   514     input := sources expressionSourcesMedium.
   499 !
   515 !
   500 
   516 
   501 setupJavaSyntax
   517 setupJavaSyntax
   502     
   518     
   503     parser := PPJavaSyntax new.
   519     parser := PPJavaSyntax new.
   504     context := PPCContext new.
   520     context := self context.
   505     context initializeFor: parser.
   521     context initializeFor: parser.
   506     input := sources javaSourcesBig.
   522     input := sources javaSourcesBig.
   507 !
   523 !
   508 
   524 
   509 setupJavaSyntaxCompiled
   525 setupJavaSyntaxCompiled
   510     parser := PPJavaSyntax new compile.
   526     parser := PPJavaSyntax new compile.
   511     context := PPCContext new.
   527     context := self context.
   512     context initializeFor: parser.
   528     context initializeFor: parser.
   513     input := sources javaSourcesBig.
   529     input := sources javaSourcesBig.
   514 
   530 
   515 "	
   531 "	
   516     size := input inject: 0 into: [:r :e | r + e size  ].
   532     size := input inject: 0 into: [:r :e | r + e size  ].
   520 !
   536 !
   521 
   537 
   522 setupLL1ExpressionGrammar
   538 setupLL1ExpressionGrammar
   523     
   539     
   524     parser := PPLL1ExpressionGrammar new.
   540     parser := PPLL1ExpressionGrammar new.
   525     context := PPCContext new.
   541     context := self context.
   526     context initializeFor: parser.
   542     context initializeFor: parser.
   527     input := sources expressionSourcesBig.
   543     input := sources expressionSourcesBig.
   528 !
   544 !
   529 
   545 
   530 setupLL1ExpressionGrammarCompiled
   546 setupLL1ExpressionGrammarCompiled
   531     
   547     
   532     configuration := PPCConfiguration universal.
   548     configuration := PPCConfiguration universal.
   533     configuration arguments name: #PPCompiledLL1ExpressionGrammar.
   549     configuration arguments name: #PPCompiledLL1ExpressionGrammar.
   534     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   550     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   535     context := PPCContext new.
   551     context := self context.
   536     context initializeFor: parser.
   552     context initializeFor: parser.
   537     input := sources expressionSourcesBig.
   553     input := sources expressionSourcesBig.
   538 !
   554 !
   539 
   555 
   540 setupLL1ExpressionGrammarTokenized
   556 setupLL1ExpressionGrammarTokenized
   541     
   557     
   542     configuration := PPCConfiguration universal.
   558     configuration := PPCConfiguration tokenizing.
   543     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   559     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   544     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   560     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   545     context := PPCContext new.
   561     context := self context.
   546     context initializeFor: parser.
   562     context initializeFor: parser.
   547     input := sources expressionSourcesBig.
   563     input := sources expressionSourcesBig.
   548 !
   564 !
   549 
   565 
   550 setupRBParser
   566 setupRBParser
   553 !
   569 !
   554 
   570 
   555 setupSmalltalkGrammar
   571 setupSmalltalkGrammar
   556     
   572     
   557     parser := PPSmalltalkGrammar new.
   573     parser := PPSmalltalkGrammar new.
   558     context := PPCContext new.
   574     context := self context.
   559     context initializeFor: parser.
   575     context initializeFor: parser.
   560     input := sources smalltalkSourcesBig.
   576     input := sources smalltalkSourcesBig.
   561 !
   577 !
   562 
   578 
   563 setupSmalltalkGrammarCompiled
   579 setupSmalltalkGrammarCompiled
   564 
   580 
   565     configuration := PPCConfiguration universal.
   581     configuration := PPCConfiguration universal.
   566     configuration arguments name: #PPCompiledSmalltalkGrammar.
   582     configuration arguments name: #PPCompiledSmalltalkGrammar.
       
   583     configuration arguments profile: profile.
       
   584     
   567     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   585     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   568     context := PPCContext new.
   586     context := self context.
   569     context initializeFor: parser.
   587     context initializeFor: parser.
   570     input := sources smalltalkSourcesBig.
   588     
       
   589     profile ifTrue: [ 
       
   590         input := sources smalltalkSourcesSmall.	
       
   591     ] ifFalse: [ 
       
   592         input := sources smalltalkSourcesBig.	
       
   593     ]
   571 !
   594 !
   572 
   595 
   573 setupSmalltalkGrammarTokenized
   596 setupSmalltalkGrammarTokenized
   574 
   597 
   575     configuration := PPCConfiguration LL1.
   598     configuration := PPCConfiguration tokenizing.
   576     configuration arguments name: #PPTokenizedSmalltalkGrammar.
   599     configuration arguments name: #PPTokenizedSmalltalkGrammar.
       
   600     configuration arguments profile: profile.
       
   601     
   577     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   602     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   578     context := PPCContext new.
   603     context := self context.
   579     context initializeFor: parser.
   604     context initializeFor: parser.
   580     input := sources smalltalkSourcesBig.
   605     profile ifTrue: [ 
       
   606         input := sources smalltalkSourcesSmall.	
       
   607     ] ifFalse: [ 
       
   608         input := sources smalltalkSourcesBig.	
       
   609     ]
   581 !
   610 !
   582 
   611 
   583 setupSmalltalkNoopParserCompiled
   612 setupSmalltalkNoopParserCompiled
   584 
   613 
   585     configuration := PPCConfiguration universal.
   614     configuration := PPCConfiguration universal.
   603 !
   632 !
   604 
   633 
   605 setupSmalltalkParser
   634 setupSmalltalkParser
   606     
   635     
   607     parser := PPSmalltalkParser new.
   636     parser := PPSmalltalkParser new.
   608     context := PPCContext new.
   637     context := self context.
   609     context initializeFor: parser.
   638     context initializeFor: parser.
   610     input := sources smalltalkSourcesBig.
   639     input := sources smalltalkSourcesBig.
   611 !
   640 !
   612 
   641 
   613 setupSmalltalkParserCompiled
   642 setupSmalltalkParserCompiled
   614 
   643 
   615     configuration := PPCConfiguration universal.
   644     configuration := PPCConfiguration universal.
   616     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   645     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   617     context := PPCContext new.
   646     context := self context.
   618     context initializeFor: parser.
   647     context initializeFor: parser.
   619     input := sources smalltalkSourcesBig.
   648     input := sources smalltalkSourcesBig.
   620 !
   649 !
   621 
   650 
   622 setupSmalltalkParserTokenized
   651 setupSmalltalkParserTokenized
   623 
   652 
   624     configuration := PPCConfiguration LL1.
   653     configuration := PPCConfiguration tokenizing.
   625     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   654     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   626     context := PPCContext new.
   655     context := self context.
   627     context initializeFor: parser.
   656     context initializeFor: parser.
   628     input := sources smalltalkSourcesBig.
   657     input := sources smalltalkSourcesBig.
   629 !
   658 !
   630 
   659 
   631 teardownExpressionGrammarTokenized
   660 teardownExpressionGrammarTokenized