compiler/benchmarks/PPCBenchmark.st
changeset 421 7e08b31e0dae
parent 420 b2f2f15cef26
child 422 116d2b2af905
equal deleted inserted replaced
420:b2f2f15cef26 421:7e08b31e0dae
     2 
     2 
     3 Object subclass:#PPCBenchmark
     3 Object subclass:#PPCBenchmark
     4 	instanceVariableNames:'sources report contextClass compile parser context input'
     4 	instanceVariableNames:'sources report contextClass compile parser context input'
     5 	classVariableNames:''
     5 	classVariableNames:''
     6 	poolDictionaries:''
     6 	poolDictionaries:''
     7 	category:'PetitCompiler-Benchmarks'
     7 	category:'PetitCompiler-Benchmarks-Core'
     8 !
     8 !
       
     9 
     9 
    10 
    10 !PPCBenchmark class methodsFor:'instance creation'!
    11 !PPCBenchmark class methodsFor:'instance creation'!
    11 
    12 
    12 new
    13 new
    13     "return an initialized instance"
    14     "return an initialized instance"
   186 	| parser |
   187 	| parser |
   187 	parser := PPJavaParser new.
   188 	parser := PPJavaParser new.
   188 	self measure: parser on: sources javaLangMath name: #java.
   189 	self measure: parser on: sources javaLangMath name: #java.
   189 !
   190 !
   190 
   191 
       
   192 benchmarkJavaSyntax
       
   193 	| time |
       
   194 	
       
   195 	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
       
   196 
       
   197 	parser := PPJavaSyntax new.
       
   198 	context := PPCContext new.
       
   199 	context initializeFor: parser.
       
   200 	input := sources javaSourcesBig.
       
   201 
       
   202 	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   203 	
       
   204 	self reportInput: input time: time name: 'Java Syntax'.
       
   205 !
       
   206 
       
   207 benchmarkJavaSyntaxCompiled
       
   208 	| time |
       
   209 	
       
   210 	self assert: '../java-src' asFileReference exists description: '../java-src directory with java sources expected'.
       
   211 
       
   212 	parser := PPJavaSyntax new compile.
       
   213 	context := PPCContext new.
       
   214 	context initializeFor: parser.
       
   215 	input := sources javaSourcesBig.
       
   216 
       
   217 	time := [ input do: [ :source | parser parse: source withContext: context ]] timeToRun asMilliSeconds.
       
   218 	
       
   219 	self reportInput: input time: time name: 'Java Syntax Compiled'.
       
   220 !
       
   221 
   191 benchmarkNegate
   222 benchmarkNegate
   192 "
   223 "
   193 	self measure: self anyStar on: sources petitParserPackage.
   224 	self measure: self anyStar on: sources petitParserPackage.
   194 "	
   225 "	
   195 	| parser |
   226 	| parser |
   284 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   315 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   285 ! !
   316 ! !
   286 
   317 
   287 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   318 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
   288 
   319 
       
   320 benchmarkJavaSyntaxC
       
   321 	<setup: #setupJavaSyntaxC>
       
   322 	<benchmark: 'Petit Java Parser - Standard'>
       
   323 	
       
   324 	input do: [ :source | parser parse: source withContext: context ]
       
   325 !
       
   326 
       
   327 benchmarkJavaSyntaxCompiledC
       
   328 	<setup: #setupJavaSyntaxCompiledC>
       
   329 	<teardown: #teardownJavaSyntaxCompiledC>
       
   330 	<benchmark: 'Petit Java Parser - Compiled'>
       
   331 	
       
   332 	input do: [ :source | parser parse: source withContext: context ]
       
   333 	
       
   334 !
       
   335 
   289 benchmarkRBParserC
   336 benchmarkRBParserC
   290 	<setup: #setupRBParserC>
   337 	<setup: #setupRBParserC>
   291 	<benchmark: 'RB Smalltalk Parser'>
   338 	<benchmark: 'RB Smalltalk Parser'>
   292 	
   339 	
   293 	input do: [ :source | RBParser parseMethod: source ]
   340 	input do: [ :source | RBParser parseMethod: source ]
   294 !
   341 !
   295 
   342 
       
   343 benchmarkSmalltalkGrammarC
       
   344 	<setup: #setupSmalltalkGrammarC>
       
   345 	<benchmark: 'Petit Smalltalk Grammar - Standard'>
       
   346 	
       
   347 	input do: [ :source | parser parse: source withContext: context ]
       
   348 !
       
   349 
       
   350 benchmarkSmalltalkGrammarCompiledC
       
   351 	<setup: #setupSmalltalkGrammarCompiledC>
       
   352 	<teardown: #teardownSmalltalkGrammarCompiledC>
       
   353 	<benchmark: 'Petit Smalltalk Grammar - Compiled'>
       
   354 	
       
   355 	
       
   356 	input do: [ :source | parser parse: source withContext: context ]
       
   357 !
       
   358 
   296 benchmarkSmalltalkParserC
   359 benchmarkSmalltalkParserC
   297 	<setup: #setupSmalltalkParserC>
   360 	<setup: #setupSmalltalkParserC>
   298 	<benchmark: 'Petit Smalltalk Parser - Standard'>
   361 	<benchmark: 'Petit Smalltalk Parser - Standard'>
   299 	
   362 	
   300 	input do: [ :source | parser parse: source withContext: context ]
   363 	input do: [ :source | parser parse: source withContext: context ]
   301 !
   364 !
   302 
   365 
   303 benchmarkSmalltalkParserCompiledC
   366 benchmarkSmalltalkParserCompiledC
   304 	<setup: #setupSmalltalkParserCompiledC>
   367 	<setup: #setupSmalltalkParserCompiledC>
   305 	<teaddown: #teardownSmalltalkParserCompiledC>
   368 	<teardown: #teardownSmalltalkParserCompiledC>
   306 	<benchmark: 'Petit Smalltalk Parser - Compiled'>
   369 	<benchmark: 'Petit Smalltalk Parser - Compiled'>
   307 	
   370 	
   308 	input do: [ :source | parser parse: source withContext: context ]
   371 	input do: [ :source | parser parse: source withContext: context ]
   309 	
   372 	
   310 ! !
   373 ! !
   350 	contextClass := aClass
   413 	contextClass := aClass
   351 ! !
   414 ! !
   352 
   415 
   353 !PPCBenchmark methodsFor:'setup & teardown-CalipeL'!
   416 !PPCBenchmark methodsFor:'setup & teardown-CalipeL'!
   354 
   417 
       
   418 setupJavaSyntaxC
       
   419 	
       
   420 	parser := PPJavaSyntax new.
       
   421 	context := PPCContext new.
       
   422 	context initializeFor: parser.
       
   423 	input := sources javaSourcesBig.
       
   424 !
       
   425 
   355 setupJavaSyntaxCompiledC
   426 setupJavaSyntaxCompiledC
   356 	parser := PPJavaSyntax new compile.
   427 	parser := PPJavaSyntax new compile.
   357 	context := PPCContext new.
   428 	context := PPCContext new.
   358 	context initializeFor: parser.
   429 	context initializeFor: parser.
   359 	input := sources javaSourcesBig.
   430 	input := sources javaSourcesBig.
   368 setupRBParserC
   439 setupRBParserC
   369 	
   440 	
   370 	input := sources smalltalkSourcesBig.
   441 	input := sources smalltalkSourcesBig.
   371 !
   442 !
   372 
   443 
       
   444 setupSmalltalkGrammarC
       
   445 	
       
   446 	parser := PPSmalltalkGrammar new.
       
   447 	context := PPCContext new.
       
   448 	context initializeFor: parser.
       
   449 	input := sources smalltalkSourcesBig.
       
   450 !
       
   451 
       
   452 setupSmalltalkGrammarCompiledC
       
   453 	parser := PPSmalltalkGrammar new compile.
       
   454 	context := PPCContext new.
       
   455 	context initializeFor: parser.
       
   456 	input := sources smalltalkSourcesBig.
       
   457 
       
   458 "	
       
   459 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   460 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   461 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   462 "
       
   463 !
       
   464 
   373 setupSmalltalkParserC
   465 setupSmalltalkParserC
   374 	
   466 	
   375 	parser := PPSmalltalkParser new.
   467 	parser := PPSmalltalkParser new.
   376 	context := PPCContext new.
   468 	context := PPCContext new.
   377 	context initializeFor: parser.
   469 	context initializeFor: parser.
   390 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   482 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   391 "
   483 "
   392 !
   484 !
   393 
   485 
   394 teardownJavaSyntaxCompiledC
   486 teardownJavaSyntaxCompiledC
       
   487 	parser class removeFromSystem.
       
   488 "	
       
   489 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   490 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   491 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   492 "
       
   493 !
       
   494 
       
   495 teardownSmalltalkGrammarCompiledC
   395 	parser class removeFromSystem.
   496 	parser class removeFromSystem.
   396 "	
   497 "	
   397 	size := input inject: 0 into: [:r :e | r + e size  ].
   498 	size := input inject: 0 into: [:r :e | r + e size  ].
   398 	Transcript crShow: 'Compiled Grammar time: ', time asString.
   499 	Transcript crShow: 'Compiled Grammar time: ', time asString.
   399 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   500 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   431 	self benchmarkJava.
   532 	self benchmarkJava.
   432 	
   533 	
   433 	self endSuite.
   534 	self endSuite.
   434 ! !
   535 ! !
   435 
   536 
       
   537 !PPCBenchmark class methodsFor:'documentation'!
       
   538 
       
   539 version_HG
       
   540 
       
   541     ^ '$Changeset: <not expanded> $'
       
   542 ! !
       
   543