compiler/benchmarks/PPCBenchmark.st
changeset 464 f6d77fee9811
parent 459 4751c407bb40
child 465 f729f6cd3c76
child 502 1e45d3c96ec5
equal deleted inserted replaced
459:4751c407bb40 464:f6d77fee9811
     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 
    55     compile := value
    55     compile := value
    56 !
    56 !
    57 
    57 
    58 measure: aParser on: anInput name: aString
    58 measure: aParser on: anInput name: aString
    59     | time result p |
    59     | time result p |
    60     context := self createContext.
    60     self halt: 'deprecated?'.
       
    61     context := self context.
    61     
    62     
    62     p := compile ifTrue: [ 
    63     p := compile ifTrue: [ 
    63         aParser end compile
    64         aParser end compile
    64     ] ifFalse: [ 
    65     ] ifFalse: [ 
    65         aParser end
    66         aParser end
    90     ((aContext rememberCount / input size) asFloat asString truncateTo: 6),
    91     ((aContext rememberCount / input size) asFloat asString truncateTo: 6),
    91     '.'.
    92     '.'.
    92 "
    93 "
    93 !
    94 !
    94 
    95 
    95 reportInput: input time: time name: name
    96 reportInput: anInput time: time name: name
    96     | size |
    97     | size |
    97     size := input inject: 0 into: [:r :e | r + e size  ].
    98     size := anInput inject: 0 into: [:r :e | r + e size  ].
    98     Transcript crShow: 'Size: ', size asString.
    99     Transcript crShow: 'Size: ', size asString.
    99     Transcript crShow: name, ' time: ', time asString.
   100     Transcript crShow: name, ' time: ', time asString.
   100     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   101     Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   102     
       
   103     (context isKindOf: PPCProfilingContext) ifTrue: [ 
       
   104         context inspect.
       
   105     ]
   101 ! !
   106 ! !
   102 
   107 
   103 !PPCBenchmark methodsFor:'benchmarks'!
   108 !PPCBenchmark methodsFor:'benchmarks'!
   104 
   109 
   105 benchmarkJavaSyntax
   110 benchmarkJavaSyntax
   128     input := sources javaSourcesBig.
   133     input := sources javaSourcesBig.
   129 
   134 
   130     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   135     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   131     
   136     
   132     self reportInput: input time: time name: 'Java Syntax Compiled'.
   137     self reportInput: input time: time name: 'Java Syntax Compiled'.
   133 !
   138 ! !
       
   139 
       
   140 !PPCBenchmark methodsFor:'benchmarks - expression grammar'!
       
   141 
       
   142 benchmarkExpressionGrammar
       
   143     | time |
       
   144 
       
   145     self setupExpressionGrammar.
       
   146 
       
   147     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   148     
       
   149     self reportInput: input time: time name: 'Expression Grammar'.
       
   150 !
       
   151 
       
   152 benchmarkExpressionGrammarCompiled
       
   153     | time |
       
   154 
       
   155     self setupExpressionGrammarCompiled.
       
   156 
       
   157     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   158     
       
   159     self reportInput: input time: time name: 'Compiled Expression Grammar'.
       
   160 !
       
   161 
       
   162 benchmarkExpressionGrammarTokenized
       
   163     | time |
       
   164 
       
   165     self setupExpressionGrammarTokenized.
       
   166 
       
   167     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   168     
       
   169     self reportInput: input time: time name: 'Tokenized Expression Grammar'.
       
   170 !
       
   171 
       
   172 benchmarkLL1ExpressionGrammar
       
   173     | time |
       
   174 
       
   175     self setupLL1ExpressionGrammar.
       
   176 
       
   177     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   178     
       
   179     self reportInput: input time: time name: 'LL1 Expression Grammar'.
       
   180 !
       
   181 
       
   182 benchmarkLL1ExpressionGrammarCompiled
       
   183     | time |
       
   184 
       
   185     self setupLL1ExpressionGrammarCompiled.
       
   186 
       
   187     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   188     
       
   189     self reportInput: input time: time name: 'Compiled LL1 Expression Grammar'.
       
   190 !
       
   191 
       
   192 benchmarkLL1ExpressionGrammarTokenized
       
   193     | time |
       
   194 
       
   195     self setupLL1ExpressionGrammarTokenized.
       
   196 
       
   197     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   198     
       
   199     self reportInput: input time: time name: 'Tokenized LL1 Expression Grammar'.
       
   200 ! !
       
   201 
       
   202 !PPCBenchmark methodsFor:'benchmarks - micro'!
       
   203 
       
   204 benchmarkAnyStar
       
   205 "
       
   206     self measure: self anyStar on: sources petitParserPackage.
       
   207 "	
       
   208     self measure: self anyStar on: (sources changesSized: 1000*1000) name: #anyStar.
       
   209 !
       
   210 
       
   211 benchmarkAnyStarBlock
       
   212 "
       
   213     self measure: self anyStar on: sources petitParserPackage.
       
   214 "	
       
   215     self measure: self anyStarBlock on: (sources changesSized: 1000*1000) name: #anyStarBlock.
       
   216 !
       
   217 
       
   218 benchmarkToken
       
   219 "
       
   220     self measure: self anyStar on: sources petitParserPackage.
       
   221 "	
       
   222     parser := (self tokenParser / #any asParser) star.
       
   223     self measure: parser on: (sources changesSized: 1000*1000) name: #token.
       
   224 ! !
       
   225 
       
   226 !PPCBenchmark methodsFor:'benchmarks - smalltalk'!
   134 
   227 
   135 benchmarkOpalCompiler
   228 benchmarkOpalCompiler
   136     | parser time input |
   229     | parser time input |
   137     parser := OpalCompiler new.
   230     parser := OpalCompiler new.
   138     input := sources smalltalkSourcesBig.
   231     input := sources smalltalkSourcesBig.
   207     input := sources smalltalkSourcesBig.
   300     input := sources smalltalkSourcesBig.
   208 
   301 
   209     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   302     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
   210     
   303     
   211         self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
   304         self reportInput: input time: time name: 'Smalltalk Parser Compiled'.
   212 ! !
       
   213 
       
   214 !PPCBenchmark methodsFor:'benchmarks - expression grammar'!
       
   215 
       
   216 benchmarkExpressionGrammar
       
   217     | time |
       
   218 
       
   219     self setupExpressionGrammar.
       
   220 
       
   221     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   222     
       
   223     self reportInput: input time: time name: 'Expression Grammar'.
       
   224 !
       
   225 
       
   226 benchmarkExpressionGrammarCompiled
       
   227     | time |
       
   228 
       
   229     self setupExpressionGrammarCompiled.
       
   230 
       
   231     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   232     
       
   233     self reportInput: input time: time name: 'Compiled Expression Grammar'.
       
   234 !
       
   235 
       
   236 benchmarkExpressionGrammarTokenized
       
   237     | time |
       
   238 
       
   239     self setupExpressionGrammarTokenized.
       
   240 
       
   241     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   242     
       
   243     self reportInput: input time: time name: 'Tokenized Expression Grammar'.
       
   244 !
       
   245 
       
   246 benchmarkLL1ExpressionGrammar
       
   247     | time |
       
   248 
       
   249     self setupLL1ExpressionGrammar.
       
   250 
       
   251     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   252     
       
   253     self reportInput: input time: time name: 'LL1 Expression Grammar'.
       
   254 !
       
   255 
       
   256 benchmarkLL1ExpressionGrammarCompiled
       
   257     | time |
       
   258 
       
   259     self setupLL1ExpressionGrammarCompiled.
       
   260 
       
   261     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   262     
       
   263     self reportInput: input time: time name: 'Compiled LL1 Expression Grammar'.
       
   264 !
       
   265 
       
   266 benchmarkLL1ExpressionGrammarTokenized
       
   267     | time |
       
   268 
       
   269     self setupLL1ExpressionGrammarTokenized.
       
   270 
       
   271     time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   272     
       
   273     self reportInput: input time: time name: 'Tokenized LL1 Expression Grammar'.
       
   274 ! !
       
   275 
       
   276 !PPCBenchmark methodsFor:'benchmarks - micro'!
       
   277 
       
   278 benchmarkAnyStar
       
   279 "
       
   280     self measure: self anyStar on: sources petitParserPackage.
       
   281 "	
       
   282     self measure: self anyStar on: (sources changesSized: 1000*1000) name: #anyStar.
       
   283 !
       
   284 
       
   285 benchmarkAnyStarBlock
       
   286 "
       
   287     self measure: self anyStar on: sources petitParserPackage.
       
   288 "	
       
   289     self measure: self anyStarBlock on: (sources changesSized: 1000*1000) name: #anyStarBlock.
       
   290 !
       
   291 
       
   292 benchmarkToken
       
   293 "
       
   294     self measure: self anyStar on: sources petitParserPackage.
       
   295 "	
       
   296     parser := (self tokenParser / #any asParser) star.
       
   297     self measure: parser on: (sources changesSized: 1000*1000) name: #token.
       
   298 ! !
   305 ! !
   299 
   306 
   300 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   307 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   301 
   308 
   302 benchmarkExpressionGrammarC
   309 benchmarkExpressionGrammarC
   379     
   386     
   380 ! !
   387 ! !
   381 
   388 
   382 !PPCBenchmark methodsFor:'intitialization'!
   389 !PPCBenchmark methodsFor:'intitialization'!
   383 
   390 
   384 createContext
   391 context
   385     ^ contextClass new
   392     ^ contextClass new
   386 !
   393 !
   387 
   394 
   388 initialize
   395 initialize
   389     super initialize.
   396     super initialize.
   390     sources := PPCResources current.
   397     sources := PPCResources current.
   391     contextClass := PPCContext.
   398     contextClass := PPCContext.
       
   399 
   392     compile := false.
   400     compile := false.
       
   401     profile := false.
   393 ! !
   402 ! !
   394 
   403 
   395 !PPCBenchmark methodsFor:'meta'!
   404 !PPCBenchmark methodsFor:'meta'!
   396 
   405 
   397 getMetaInfo: key
   406 getMetaInfo: key
   422 
   431 
   423 tokenParser
   432 tokenParser
   424     ^ #letter asParser, (#letter asParser / #digit asParser) star trim
   433     ^ #letter asParser, (#letter asParser / #digit asParser) star trim
   425 ! !
   434 ! !
   426 
   435 
       
   436 !PPCBenchmark methodsFor:'profiling'!
       
   437 
       
   438 profile
       
   439     contextClass := PPCProfilingContext.
       
   440     profile := true.
       
   441 ! !
       
   442 
   427 !PPCBenchmark methodsFor:'setup & teardown'!
   443 !PPCBenchmark methodsFor:'setup & teardown'!
   428 
   444 
   429 setupExpressionGrammar
   445 setupExpressionGrammar
   430     
   446     
   431     parser := PPExpressionGrammar new.
   447     parser := PPExpressionGrammar new.
   432     context := PPCContext new.
   448     context := self context.
   433     context initializeFor: parser.
   449     context initializeFor: parser.
   434     input := sources expressionSourcesMedium.
   450     input := sources expressionSourcesMedium.
   435 !
   451 !
   436 
   452 
   437 setupExpressionGrammarCompiled
   453 setupExpressionGrammarCompiled
   438     
   454     
   439     configuration := PPCConfiguration universal.
   455     configuration := PPCConfiguration universal.
   440     configuration arguments name: #PPCompiledExpressionGrammar.
   456     configuration arguments name: #PPCompiledExpressionGrammar.
   441     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   457     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   442     context := PPCContext new.
   458     context := self context.
   443     context initializeFor: parser.
   459     context initializeFor: parser.
   444     input := sources expressionSourcesMedium.
   460     input := sources expressionSourcesMedium.
   445 !
   461 !
   446 
   462 
   447 setupExpressionGrammarTokenized
   463 setupExpressionGrammarTokenized
   448     
   464     
   449     configuration := PPCConfiguration LL1.
   465     configuration := PPCConfiguration tokenizing.
   450     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   466     configuration arguments name: #PPTokenizedExpressionGrammar.
   451     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   467     parser := PPExpressionGrammar new compileWithConfiguration: configuration.
   452     context := PPCContext new.
   468     context := self context.
   453     context initializeFor: parser.
   469     context initializeFor: parser.
   454     input := sources expressionSourcesMedium.
   470     input := sources expressionSourcesMedium.
   455 !
   471 !
   456 
   472 
   457 setupJavaSyntax
   473 setupJavaSyntax
   458     
   474     
   459     parser := PPJavaSyntax new.
   475     parser := PPJavaSyntax new.
   460     context := PPCContext new.
   476     context := self context.
   461     context initializeFor: parser.
   477     context initializeFor: parser.
   462     input := sources javaSourcesBig.
   478     input := sources javaSourcesBig.
   463 !
   479 !
   464 
   480 
   465 setupJavaSyntaxCompiled
   481 setupJavaSyntaxCompiled
   466     parser := PPJavaSyntax new compile.
   482     parser := PPJavaSyntax new compile.
   467     context := PPCContext new.
   483     context := self context.
   468     context initializeFor: parser.
   484     context initializeFor: parser.
   469     input := sources javaSourcesBig.
   485     input := sources javaSourcesBig.
   470 
   486 
   471 "	
   487 "	
   472     size := input inject: 0 into: [:r :e | r + e size  ].
   488     size := input inject: 0 into: [:r :e | r + e size  ].
   476 !
   492 !
   477 
   493 
   478 setupLL1ExpressionGrammar
   494 setupLL1ExpressionGrammar
   479     
   495     
   480     parser := PPLL1ExpressionGrammar new.
   496     parser := PPLL1ExpressionGrammar new.
   481     context := PPCContext new.
   497     context := self context.
   482     context initializeFor: parser.
   498     context initializeFor: parser.
   483     input := sources expressionSourcesBig.
   499     input := sources expressionSourcesBig.
   484 !
   500 !
   485 
   501 
   486 setupLL1ExpressionGrammarCompiled
   502 setupLL1ExpressionGrammarCompiled
   487     
   503     
   488     configuration := PPCConfiguration universal.
   504     configuration := PPCConfiguration universal.
   489     configuration arguments name: #PPCompiledLL1ExpressionGrammar.
   505     configuration arguments name: #PPCompiledLL1ExpressionGrammar.
   490     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   506     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   491     context := PPCContext new.
   507     context := self context.
   492     context initializeFor: parser.
   508     context initializeFor: parser.
   493     input := sources expressionSourcesBig.
   509     input := sources expressionSourcesBig.
   494 !
   510 !
   495 
   511 
   496 setupLL1ExpressionGrammarTokenized
   512 setupLL1ExpressionGrammarTokenized
   497     
   513     
   498     configuration := PPCConfiguration universal.
   514     configuration := PPCConfiguration tokenizing.
   499     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   515     configuration arguments name: #PPTokenizedLL1ExpressionGrammar.
   500     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   516     parser := PPLL1ExpressionGrammar new compileWithConfiguration: configuration.
   501     context := PPCContext new.
   517     context := self context.
   502     context initializeFor: parser.
   518     context initializeFor: parser.
   503     input := sources expressionSourcesBig.
   519     input := sources expressionSourcesBig.
   504 !
   520 !
   505 
   521 
   506 setupRBParser
   522 setupRBParser
   509 !
   525 !
   510 
   526 
   511 setupSmalltalkGrammar
   527 setupSmalltalkGrammar
   512     
   528     
   513     parser := PPSmalltalkGrammar new.
   529     parser := PPSmalltalkGrammar new.
   514     context := PPCContext new.
   530     context := self context.
   515     context initializeFor: parser.
   531     context initializeFor: parser.
   516     input := sources smalltalkSourcesBig.
   532     input := sources smalltalkSourcesBig.
   517 !
   533 !
   518 
   534 
   519 setupSmalltalkGrammarCompiled
   535 setupSmalltalkGrammarCompiled
   520 
   536 
   521     configuration := PPCConfiguration universal.
   537     configuration := PPCConfiguration universal.
   522     configuration arguments name: #PPCompiledSmalltalkGrammar.
   538     configuration arguments name: #PPCompiledSmalltalkGrammar.
       
   539     configuration arguments profile: profile.
       
   540     
   523     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   541     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   524     context := PPCContext new.
   542     context := self context.
   525     context initializeFor: parser.
   543     context initializeFor: parser.
   526     input := sources smalltalkSourcesBig.
   544     
       
   545     profile ifTrue: [ 
       
   546         input := sources smalltalkSourcesSmall.	
       
   547     ] ifFalse: [ 
       
   548         input := sources smalltalkSourcesBig.	
       
   549     ]
   527 !
   550 !
   528 
   551 
   529 setupSmalltalkGrammarTokenized
   552 setupSmalltalkGrammarTokenized
   530 
   553 
   531     configuration := PPCConfiguration LL1.
   554     configuration := PPCConfiguration tokenizing.
   532     configuration arguments name: #PPTokenizedSmalltalkGrammar.
   555     configuration arguments name: #PPTokenizedSmalltalkGrammar.
       
   556     configuration arguments profile: profile.
       
   557     
   533     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   558     parser := PPSmalltalkGrammar new compileWithConfiguration: configuration.
   534     context := PPCContext new.
   559     context := self context.
   535     context initializeFor: parser.
   560     context initializeFor: parser.
   536     input := sources smalltalkSourcesBig.
   561     profile ifTrue: [ 
       
   562         input := sources smalltalkSourcesSmall.	
       
   563     ] ifFalse: [ 
       
   564         input := sources smalltalkSourcesBig.	
       
   565     ]
   537 !
   566 !
   538 
   567 
   539 setupSmalltalkParser
   568 setupSmalltalkParser
   540     
   569     
   541     parser := PPSmalltalkParser new.
   570     parser := PPSmalltalkParser new.
   542     context := PPCContext new.
   571     context := self context.
   543     context initializeFor: parser.
   572     context initializeFor: parser.
   544     input := sources smalltalkSourcesBig.
   573     input := sources smalltalkSourcesBig.
   545 !
   574 !
   546 
   575 
   547 setupSmalltalkParserCompiled
   576 setupSmalltalkParserCompiled
   548 
   577 
   549     configuration := PPCConfiguration universal.
   578     configuration := PPCConfiguration universal.
   550     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   579     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   551     context := PPCContext new.
   580     context := self context.
   552     context initializeFor: parser.
   581     context initializeFor: parser.
   553     input := sources smalltalkSourcesBig.
   582     input := sources smalltalkSourcesBig.
   554 !
   583 !
   555 
   584 
   556 setupSmalltalkParserTokenized
   585 setupSmalltalkParserTokenized
   557 
   586 
   558     configuration := PPCConfiguration LL1.
   587     configuration := PPCConfiguration tokenizing.
   559     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   588     parser := PPSmalltalkParser new compileWithConfiguration: configuration.
   560     context := PPCContext new.
   589     context := self context.
   561     context initializeFor: parser.
   590     context initializeFor: parser.
   562     input := sources smalltalkSourcesBig.
   591     input := sources smalltalkSourcesBig.
   563 !
   592 !
   564 
   593 
   565 teardownExpressionGrammarTokenized
   594 teardownExpressionGrammarTokenized