s/BenchmarkExecutor.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 10 Mar 2014 11:29:09 +0000
changeset 206 29602f0696d8
parent 186 d444d8e7d29b
child 207 1697e4572960
permissions -rw-r--r--
Refactoring and cleanup. * Support for multiple per-benchmark setups. * Fix for overridden parameter definitions. * Fix in parameter combinator. When parameter has no default value but possible values are listed and no value is explicitly defined (using -D), then run benchmark with all values listed in parameter definition. * Run setup/teardown before and after **EACH** benchmark run and before/after warmup.

"{ Package: 'jv:calipel/s' }"

Object subclass:#BenchmarkExecutor
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'CalipeL-S-Core'
!

!BenchmarkExecutor class methodsFor:'documentation'!

documentation
"
    A benchmark executor takes a signle BenchmarkInstance and a set of
    parameter definitions and executes it. Returns a set of
    BenchmarkOutcomes.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!BenchmarkExecutor class methodsFor:'execution'!

execute:aBenchmarkInstance
    ^ self new execute:aBenchmarkInstance
!

execute:aBenchmarkInstance result:aBenchmarkResult
    ^ self new execute:aBenchmarkInstance result:aBenchmarkResult
!

execute:aBenchmarkInstance result:aBenchmarkResult defines:aDictionary
    ^ self new execute:aBenchmarkInstance result:aBenchmarkResult defines:aDictionary
! !

!BenchmarkExecutor methodsFor:'executing'!

execute: aBenchmarkInstance
    "Executes the benchmark and returns the result (timings)"

    ^ self execute: aBenchmarkInstance result: BenchmarkResult new

    "Created: / 09-03-2014 / 10:59:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

execute: aBenchmarkInstance result: aBenchmarkResult
    "
    Executes the benchmark and adds results into given resultset
    "

    ^ self execute: aBenchmarkInstance result: aBenchmarkResult defines: Dictionary new.

    "Created: / 09-03-2014 / 10:59:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

execute: aBenchmarkInstance result: aBenchmarkResult defines: aDictionary
    "
    Takes a benchmark instance and a set of parameter defines,
    executes the benchmark and one or more outcomes into given
    result.

    This is where real execution happens"

    | parameters combinator |

    aBenchmarkResult initializeTimestampIfNotAlready.
    parameters := aBenchmarkInstance parameters collect:[:parameter|
        | key1 key2 valuesString values defined |

        key1 := aBenchmarkInstance instance class name , '#' , parameter name.
        key2 := parameter name.
        defined := true.
        valuesString := aDictionary at: key1 ifAbsent:[aDictionary at: key2 ifAbsent:[defined := false]].
        defined ifTrue:[
            values := BenchmarkPlatform current isSmalltalkX 
                        ifTrue:[valuesString tokensBasedOn: $,]
                        ifFalse:[valuesString subStrings:','].
            values := values collect:[:each|

                (parameter type includesBehavior: String) ifTrue:[
                    each
                ] ifFalse:[
                    | s v |

                    s := each readStream.
                    v := parameter type readFrom: s onError:[
                        "JV: Note for Smalltalk/X: #signal: is actually an ANSI 1.9 protocol!!"
                        BenchmarkParameterError new signal: 'Cannot read parameter value for ' , parameter name , ' (parse error)'
                    ].
                    s atEnd ifFalse:[
                        "JV: Note for Smalltalk/X: #signal: is actually an ANSI 1.9 protocol!!"
                        BenchmarkParameterError new signal: 'Cannot read parameter value for ' , parameter name , ' (parse error)'
                    ].
                    v.                
                ].
            ]

        ] ifFalse:[
            parameter default == BenchmarkParameter undefinedValue ifTrue:[
                values := parameter values.
                values isNil ifTrue:[ 
                    BenchmarkParameterError new signal: 'Parameter value not defined and default value(s) not specified for' , parameter name.
                ].
            ] ifFalse:[ 
                values := Array with: parameter default.    
            ].
        ].
        parameter -> values
    ].

    parameters := parameters asOrderedCollection sort:[:a :b | a key name < b key name ].

    combinator := [:parametersAndValues |
        parametersAndValues size = parameters size ifTrue:[
            self execute: aBenchmarkInstance  result: aBenchmarkResult  parameters: parametersAndValues.
        ] ifFalse:[
            | parameter |

            parameter := parameters at: parametersAndValues size + 1.
            parameter value do:[:value |
                combinator value: (parametersAndValues copyWith: (parameter key -> value)).
            ]
        ]
    ].

    combinator value: #().

    "Created: / 12-08-2013 / 00:11:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-03-2014 / 10:23:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BenchmarkExecutor methodsFor:'executing-private'!

execute: aBenchmarkInstance result: aBenchmarkResult parameters: aCollection
    "
    Takes a benchmark instance and a set of parameter defines,
    executes the benchmark and an outcome to the result. Returns that
    outcome

    This is where real execution happens"

    | times outcome |

    "First, warm it up"
    [ 
        self setUp:aBenchmarkInstance parameters: aCollection.  
        self warmUp: aBenchmarkInstance.
    ] ensure:[
        self tearDown: aBenchmarkInstance
    ].

    times := (1 to: aBenchmarkResult runs) collect:[:i | 
        [
            self setUp:aBenchmarkInstance parameters: aCollection.  
            self timeIt: aBenchmarkInstance 
        ] ensure:[
            self tearDown: aBenchmarkInstance
        ].
    ].

    aBenchmarkResult addOutcome:
        (outcome := BenchmarkOutcome 
            benchmark: aBenchmarkInstance
            times: times
            parameters: aCollection).

    ^ outcome

    "Created: / 27-07-2013 / 12:32:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 10-03-2014 / 09:36:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setUp:aBenchmarkInstance parameters: aCollection
    [
        aCollection do:[:each|
            aBenchmarkInstance setUpParameter: each key value: each value
        ].
        aBenchmarkInstance setUp.        
    ] on: Error do:[:ex|
        (ex isKindOf: BenchmarkError) ifTrue:[
            ex pass
        ] ifFalse:[
            BenchmarkExecutionError new signal:'Error during set-up: ', ex description.
        ].

    ]

    "Created: / 27-07-2013 / 12:31:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-08-2013 / 19:14:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

tearDown: aBenchmarkInstance
    [
        aBenchmarkInstance tearDown.
    ] on: Error do:[:ex|
        BenchmarkExecutionError new signal:'Error during tear-down: ', ex description.      
    ]

    "Created: / 24-06-2013 / 01:12:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-07-2013 / 01:03:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

timeIt: aBenchmarkInstance
    | t |
    [
        t := aBenchmarkInstance timeIt.
    ] on: Error do:[:ex|
        BenchmarkExecutionError new signal:'Error during measurement: ', ex description.      
    ].
    ^t

    "Created: / 24-06-2013 / 01:11:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-07-2013 / 01:03:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

warmUp: aBenchmarkInstance
    [
        aBenchmarkInstance warmUp.
    ] on: Error do:[:ex|
        BenchmarkExecutionError new signal:'Error during warm-up: ', ex description.      
    ]

    "Created: / 24-06-2013 / 01:11:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-07-2013 / 01:04:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BenchmarkExecutor class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !