compiler/PPCBenchmark.st
changeset 414 0eaf09920532
parent 413 5389e6fbb3bc
equal deleted inserted replaced
413:5389e6fbb3bc 414:0eaf09920532
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     2 
     2 
     3 Object subclass:#PPCBenchmark
     3 Object subclass:#PPCBenchmark
     4 	instanceVariableNames:'sources report contextClass compile'
     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'
     8 !
     8 !
     9 
     9 
    13     "return an initialized instance"
    13     "return an initialized instance"
    14 
    14 
    15     ^ self basicNew initialize.
    15     ^ self basicNew initialize.
    16 ! !
    16 ! !
    17 
    17 
       
    18 !PPCBenchmark class methodsFor:'benchmarking-CalipeL'!
       
    19 
       
    20 run
       
    21 	| benchmarkSuiteClass |
       
    22 	
       
    23 	benchmarkSuiteClass := Smalltalk at: #BenchmarkSuite.
       
    24 	benchmarkSuiteClass isNil ifTrue:[
       
    25 		self error: 'CalipeL is not loaded.'
       
    26 	].
       
    27 	^ (benchmarkSuiteClass  class:self) run
       
    28 
       
    29   	"
       
    30 	PPCBenchmark run.
       
    31 	"
       
    32 !
       
    33 
       
    34 run: selector
       
    35 	| benchmarkSuiteClass |
       
    36 	
       
    37 	benchmarkSuiteClass := Smalltalk at: #BenchmarkSuite.
       
    38 	benchmarkSuiteClass isNil ifTrue:[
       
    39 		self error: 'CalipeL is not loaded.'
       
    40 	].
       
    41 	^ (benchmarkSuiteClass  class:self selector: selector ) run
       
    42 	
       
    43 	"
       
    44 	PPCBenchmark run: #benchmarkRBParserC
       
    45 	"
       
    46 ! !
       
    47 
    18 !PPCBenchmark methodsFor:'benchmark support'!
    48 !PPCBenchmark methodsFor:'benchmark support'!
    19 
    49 
    20 createContext
    50 createContext
    21 	^ contextClass new
    51 	^ contextClass new
    22 !
    52 !
    23 
    53 
    24 endSuite
    54 endSuite
    25 !
    55 !
    26 
    56 
    27 initialize
    57 initialize
    28     super initialize.
    58 	super initialize.
    29     sources := PPCBenchmarkResources new.
    59 	sources := PPCBenchmarkResources new.
    30     contextClass := PPCContext.
    60 	contextClass := PPCContext.
    31     compile := false.
    61 	compile := false.
    32 !
    62 !
    33 
    63 
    34 measure: parser on: input
    64 measure: parser on: input
    35 	self measure: parser on: input name: #unknown
    65 	self measure: parser on: input name: #unknown
    36 !
    66 !
    37 
    67 
    38 measure: parser on: input name: aString
    68 measure: aParser on: anInput name: aString
    39 	| time result context p |
    69 	| time result p |
    40 	context := self createContext.
    70 	context := self createContext.
    41 	
    71 	
    42 	compile 	ifTrue: [ 
    72 	compile 	ifTrue: [ 
    43 					p := (parser end compile: #TmpBenchmark) 
    73 					p := (aParser end compile: #TmpBenchmark) 
    44 				] ifFalse: [ 
    74 				] ifFalse: [ 
    45 					p := parser end. 
    75 					p := aParser end. 
    46 				].
    76 				].
    47 
    77 
    48 	
    78 	
    49 	time := Time millisecondsToRun: [ result := p parse: input withContext: context ].
    79 	time := Time millisecondsToRun: [ result := p parse: anInput withContext: context ].
    50 
    80 
    51 	self assert: result isPetitFailure not.
    81 	self assert: result isPetitFailure not.
    52 	self reportFor: parser context: context input: input time: time name: aString.
    82 	self reportFor: aParser context: context input: anInput time: time name: aString.
    53 !
    83 !
    54 
    84 
    55 measure: parser onSources: inputs name: aString
    85 measure: parser onSources: inputs name: aString
    56 	| time result context p totalInput |
    86 	| time result context p totalInput |
    57 	
    87 	
    76 
   106 
    77 reportFor: parser context: context input: input time: time
   107 reportFor: parser context: context input: input time: time
    78 	self reportFor: parser context: context input: input time: time name: #unknown
   108 	self reportFor: parser context: context input: input time: time name: #unknown
    79 !
   109 !
    80 
   110 
    81 reportFor: parser context: context input: input time: time name: name
   111 reportFor: aParser context: aContext input: anInput time: time name: name
    82 	Transcript crShow: (self getMetaInfo: name).
   112 	Transcript crShow: (self getMetaInfo: name).
    83 	Transcript crShow: '	Compile: ', compile asString.	
   113 	Transcript crShow: '	Compile: ', compile asString.	
    84 	
   114 	
    85 	Transcript crShow: '	Total time: ', time asString, ' ms'.
   115 	Transcript crShow: '	Total time: ', time asString, ' ms'.
    86 		
   116 		
    87 	Transcript crShow: '	Time per character: ', 
   117 	Transcript crShow: '	Time per character: ', 
    88 	(((time / input size) asFloat * 1000) asString truncateTo: 6), 
   118 	(((time / anInput size) asFloat * 1000) asString truncateTo: 6), 
    89 	' microseconds'.
   119 	' microseconds'.
    90 	
   120 	
    91 	Transcript crShow: '	Backtrack per character: ',
   121 "	Transcript crShow: '	Backtrack per character: ',
    92 	((context backtrackCount / input size) asFloat asString truncateTo: 6),
   122 	((aContext backtrackCount / anInput size) asFloat asString truncateTo: 6),
    93 	'.'.
   123 	'.'.
    94 	
   124 	
    95 	Transcript crShow: '	Remembers per character: ',
   125 	Transcript crShow: '	Remembers per character: ',
    96 	((context rememberCount / input size) asFloat asString truncateTo: 6),
   126 	((aContext rememberCount / input size) asFloat asString truncateTo: 6),
    97 	'.'.
   127 	'.'.
       
   128 "
    98 !
   129 !
    99 
   130 
   100 startSuite
   131 startSuite
   101 	Transcript crShow: Date current asString, ' ', Time current asString.
   132 	Transcript crShow: Date current asString, ' ', Time current asString.
   102 ! !
   133 ! !
   105 
   136 
   106 benchmarkAnyStar
   137 benchmarkAnyStar
   107 "
   138 "
   108 	self measure: self anyStar on: sources petitParserPackage.
   139 	self measure: self anyStar on: sources petitParserPackage.
   109 "	
   140 "	
   110 	self measure: self anyStar on: (self changesSized: 1000*1000) name: #anyStar.
   141 	self measure: self anyStar on: (sources changesSized: 1000*1000) name: #anyStar.
       
   142 !
       
   143 
       
   144 benchmarkAnyStarBlock
       
   145 "
       
   146 	self measure: self anyStar on: sources petitParserPackage.
       
   147 "	
       
   148 	self measure: self anyStarBlock on: (sources changesSized: 1000*1000) name: #anyStarBlock.
   111 !
   149 !
   112 
   150 
   113 benchmarkAttributes
   151 benchmarkAttributes
   114 	| string text allStyles |
   152 	| string text allStyles |
   115 	string := (self changesSized: 60000).
   153 	string := (self changesSized: 60000).
   167 	
   205 	
   168 	self reportInput: input time: time name: 'Opal'
   206 	self reportInput: input time: time name: 'Opal'
   169 !
   207 !
   170 
   208 
   171 benchmarkSmalltalkGrammar
   209 benchmarkSmalltalkGrammar
   172 	| parser time input context |
   210 	| time |
       
   211 
   173 	parser := PPSmalltalkGrammar new.
   212 	parser := PPSmalltalkGrammar new.
   174 	context := PPContext new.
   213 	context := PPContext new.
   175 	context initializeFor: parser.
   214 	context initializeFor: parser.
   176 	input := sources smalltalkSourcesBig.
   215 	input := sources smalltalkSourcesBig.
   177 
   216 
   179 	
   218 	
   180 	self reportInput: input time: time name: 'Smalltalk Grammar'.
   219 	self reportInput: input time: time name: 'Smalltalk Grammar'.
   181 !
   220 !
   182 
   221 
   183 benchmarkSmalltalkGrammarCompiled
   222 benchmarkSmalltalkGrammarCompiled
   184 	| parser time input context  |
   223 	| time  |
   185 	parser := PPSmalltalkGrammar new compile.
   224 	parser := PPSmalltalkGrammar new compile.
   186 	context := PPCContext new.
   225 	context := PPCContext new.
   187 	context initializeFor: parser.
   226 	context initializeFor: parser.
   188 	input := sources smalltalkSourcesBig.
   227 	input := sources smalltalkSourcesBig.
   189 
   228 
   203 	parser := PPSmalltalkGrammar new.
   242 	parser := PPSmalltalkGrammar new.
   204 	self measure: parser onSources: sources smalltalkObjectMethods name: #smalltalkObject.
   243 	self measure: parser onSources: sources smalltalkObjectMethods name: #smalltalkObject.
   205 !
   244 !
   206 
   245 
   207 benchmarkSmalltalkParser
   246 benchmarkSmalltalkParser
   208 	| parser time input context |
   247 	| time |
   209 	parser := PPSmalltalkParser new.
   248 	parser := PPSmalltalkParser new.
   210 	context := PPContext new.
   249 	context := PPContext new.
   211 	context initializeFor: parser.
   250 	context initializeFor: parser.
   212 	input := sources smalltalkSourcesBig.
   251 	input := sources smalltalkSourcesBig.
   213 
   252 
   215 	
   254 	
   216 	self reportInput: input time: time name: 'Smalltalk Parser'.
   255 	self reportInput: input time: time name: 'Smalltalk Parser'.
   217 !
   256 !
   218 
   257 
   219 benchmarkSmalltalkParserCompiled
   258 benchmarkSmalltalkParserCompiled
   220 	| parser time input context |
   259 	| time |
   221 	parser := PPSmalltalkParser new compile.
   260 	parser := PPSmalltalkParser new compile.
   222 	context := PPCContext new.
   261 	context := PPCContext new.
   223 	context initializeFor: parser.
   262 	context initializeFor: parser.
   224 	input := sources smalltalkSourcesBig.
   263 	input := sources smalltalkSourcesBig.
   225 
   264 
   241 	| size |
   280 	| size |
   242 	size := input inject: 0 into: [:r :e | r + e size  ].
   281 	size := input inject: 0 into: [:r :e | r + e size  ].
   243 	Transcript crShow: 'Size: ', size asString.
   282 	Transcript crShow: 'Size: ', size asString.
   244 	Transcript crShow: name, ' time: ', time asString.
   283 	Transcript crShow: name, ' time: ', time asString.
   245 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
   284 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   285 ! !
       
   286 
       
   287 !PPCBenchmark methodsFor:'benchmarks-CalipeL'!
       
   288 
       
   289 benchmarkRBParserC
       
   290 	<setup: #setupRBParserC>
       
   291 	<benchmark: 'RB Smalltalk Parser'>
       
   292 	
       
   293 	input do: [ :source | RBParser parseMethod: source ]
       
   294 !
       
   295 
       
   296 benchmarkSmalltalkParserC
       
   297 	<setup: #setupSmalltalkParserC>
       
   298 	<benchmark: 'Petit Smalltalk Parser - Standard'>
       
   299 	
       
   300 	input do: [ :source | parser parse: source withContext: context ]
       
   301 !
       
   302 
       
   303 benchmarkSmalltalkParserCompiledC
       
   304 	<setup: #setupSmalltalkParserCompiledC>
       
   305 	<teaddown: #teardownSmalltalkParserCompiledC>
       
   306 	<benchmark: 'Petit Smalltalk Parser - Compiled'>
       
   307 	
       
   308 	input do: [ :source | parser parse: source withContext: context ]
       
   309 	
   246 ! !
   310 ! !
   247 
   311 
   248 !PPCBenchmark methodsFor:'meta'!
   312 !PPCBenchmark methodsFor:'meta'!
   249 
   313 
   250 getMetaInfo: key
   314 getMetaInfo: key
   256 
   320 
   257 metaInfo
   321 metaInfo
   258 	^ { 
   322 	^ { 
   259 		#anyStar -> '.* Parser'.
   323 		#anyStar -> '.* Parser'.
   260 		#token -> 'Token Parser'.
   324 		#token -> 'Token Parser'.
   261 		#backtrack -> 'Backtracking Parser'.
   325 		#anyStarBlock -> 'context next in loop'.
   262 		#negate -> 'Negate Parser'.
       
   263 		#java -> 'Standard Java Parser'.
       
   264 		#smalltalkObject -> 'All Smalltalk Object methods'
       
   265 	}
   326 	}
   266 ! !
   327 ! !
   267 
   328 
   268 !PPCBenchmark methodsFor:'parsers'!
   329 !PPCBenchmark methodsFor:'parsers'!
   269 
   330 
   270 anyStar
   331 anyStar
   271 	^ #any asParser star
   332 	^ #any asParser star
   272 !
   333 !
   273 
   334 
       
   335 anyStarBlock
       
   336 	^ [ :ctx | [ctx atEnd] whileFalse: [ ctx next ] ] asParser
       
   337 !
       
   338 
   274 tokenParser
   339 tokenParser
   275 	^ #letter asParser, (#letter asParser / #digit asParser) star trim
   340 	^ #letter asParser, (#letter asParser / #digit asParser) star trim
   276 ! !
   341 ! !
   277 
   342 
   278 !PPCBenchmark methodsFor:'settings'!
   343 !PPCBenchmark methodsFor:'settings'!
   281 	compile := aBoolean
   346 	compile := aBoolean
   282 !
   347 !
   283 
   348 
   284 contextClass: aClass
   349 contextClass: aClass
   285 	contextClass := aClass
   350 	contextClass := aClass
       
   351 ! !
       
   352 
       
   353 !PPCBenchmark methodsFor:'setup & teardown-CalipeL'!
       
   354 
       
   355 setupJavaSyntaxCompiledC
       
   356 	parser := PPJavaSyntax new compile.
       
   357 	context := PPCContext new.
       
   358 	context initializeFor: parser.
       
   359 	input := sources javaSourcesBig.
       
   360 
       
   361 "	
       
   362 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   363 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   364 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   365 "
       
   366 !
       
   367 
       
   368 setupRBParserC
       
   369 	
       
   370 	input := sources smalltalkSourcesBig.
       
   371 !
       
   372 
       
   373 setupSmalltalkParserC
       
   374 	
       
   375 	parser := PPSmalltalkParser new.
       
   376 	context := PPCContext new.
       
   377 	context initializeFor: parser.
       
   378 	input := sources smalltalkSourcesBig.
       
   379 !
       
   380 
       
   381 setupSmalltalkParserCompiledC
       
   382 	parser := PPSmalltalkParser new compile.
       
   383 	context := PPCContext new.
       
   384 	context initializeFor: parser.
       
   385 	input := sources smalltalkSourcesBig.
       
   386 
       
   387 "	
       
   388 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   389 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   390 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   391 "
       
   392 !
       
   393 
       
   394 teardownJavaSyntaxCompiledC
       
   395 	parser class removeFromSystem.
       
   396 "	
       
   397 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   398 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   399 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   400 "
       
   401 !
       
   402 
       
   403 teardownSmalltalkParserCompiledC
       
   404 	parser class removeFromSystem.
       
   405 "	
       
   406 	size := input inject: 0 into: [:r :e | r + e size  ].
       
   407 	Transcript crShow: 'Compiled Grammar time: ', time asString.
       
   408 	Transcript crShow: 'Time per character: ', (time / size * 1000.0) asString, ' microseconds'.
       
   409 "
   286 ! !
   410 ! !
   287 
   411 
   288 !PPCBenchmark methodsFor:'sources'!
   412 !PPCBenchmark methodsFor:'sources'!
   289 
   413 
   290 changesSized: size
   414 changesSized: size