reports/Builder__ReportRunner.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 13 Jan 2012 11:07:57 +0100
changeset 72 c23d29fe0ec6
child 77 90d1dd533087
permissions -rw-r--r--
initial checkin

"{ Package: 'stx:goodies/builder/reports' }"

"{ NameSpace: Builder }"

StandaloneStartup subclass:#ReportRunner
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Builder-Reports'
!

ReportRunner class instanceVariableNames:'parser report debugging'

"
 The following class instance variables are inherited by this class:

	StandaloneStartup - MutexHandle
	Object - 
"
!


!ReportRunner class methodsFor:'initialization'!

initialize

    super initialize.
    debugging := Transcript notNil and:[Transcript isView].

    "Created: / 06-11-2011 / 22:07:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'command line options'!

cmdlineOptionOutputDirectory

    ^CmdLineOption new
        short: $D;
        long: 'output-directory';
        description: 'Default report output directory';
        action:[:outputdir | 
            Report outputDir: outputdir.
            self  verboseInfo:'Report dir: ' , Report outputDir asString.
        ]

    "Created: / 06-11-2011 / 09:33:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

cmdlineOptionReport

    ^CmdLineOption new
        short: $r;
        long: '--report';
        description: 'Report to run';
        action:[:option |
            report := Smalltalk at: option asSymbol.
            report isNil ifTrue:[
                Stderr nextPutLine:('ERROR: Report class %1 does not exist (forgot to load package)' bindWith: option).        
                "/Smalltalk exit: 1.        
            ].
            report := report new.
            parser options addAll: (CmdLineOption optionsFor: report)
        ]

    "Created: / 06-11-2011 / 09:45:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'defaults'!

allowDebugOption

    ^true

    "Created: / 21-07-2011 / 09:48:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'multiple applications support'!

applicationRegistryPath
    "the key under which this application stores its process ID in the registry
     as a collection of path-components.
     i.e. if #('foo' 'bar' 'baz') is returned here, the current applications ID will be stored
     in HKEY_CURRENT_USER\Software\foo\bar\baz\CurrentID.
     (would also be used as a relative path for a temporary lock file under unix).
     Used to detect if another instance of this application is already running."

    ^ #('exept' 'smalltallx' 'hdreportrunner')

    "Modified: / 21-07-2011 / 09:43:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

applicationUUID
    "answer an application-specific unique uuid.
     This is used as the name of some exclusive OS-resource, which is used to find out,
     if another instance of this application is already running.
     Under win32, a mutex is used; under unix, an exclusive file in the tempDir could be used."

    ^ '99f65c80-b375-11e0-86ad-0013e89c0459' asUUID

    "Modified: / 21-07-2011 / 09:44:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'startup'!

setupToolsForDebug

    super setupToolsForDebug.
    debugging := true.

    "Created: / 06-11-2011 / 22:06:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'startup-to be redefined'!

main:argv 

    "Process command line arguments"
    parser := CmdLineParser new.
    [               
        parser parse: argv for: self.        
    ] on: Error do:[:ex|
        Stderr nextPutLine:'Error when processing options: ', ex description.
        debugging ifFalse:[
            Stderr nextPutLine:'Exiting'.
            Smalltalk exit:1.
        ] ifTrue:[
            ex pass
        ]        
    ].

    [
        report run.
        debugging ifFalse:[
            Smalltalk exit:0.
        ].
    ] on: Error do:[:ex|
        Stderr nextPutAll:'Error when running tests: '.
        Stderr nextPutAll:ex description; cr.
        ex suspendedContext printAllOn:Stderr.
        debugging ifFalse:[
            Smalltalk exit:1.
        ] ifTrue:[
            ex pass
        ]
    ]

    "Modified: / 07-11-2011 / 09:26:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

old_main:argv 
    |argc reports outputDir i|

    argc := argv size.
    outputDir := Smalltalk commandLineArgumentNamed:'-o'.
    outputDir 
        ifNil:[outputDir := Smalltalk commandLineArgumentNamed:'--out-dir'.].
    outputDir 
        ifNotNil:[
            outputDir asFilename exists ifFalse:[
                outputDir asFilename recursiveMakeDirectory
            ].
            Report outputDir:outputDir.
        ].
    self 
        verboseInfo:'Report dir: ' , (Smalltalk at:#'Builder::Report:OutputDir') asString.
    reports := OrderedCollection new.
    i := 1.
    [
        [
            i := argv indexOf:'-r' startingAt:i.
            i ~~ 0 and:[i < argc]
        ] whileTrue:[
            |reportName formatName report|

            reportName := argv at:i + 1.
            i := i + 2.
            (report := Smalltalk at:reportName asSymbol) 
                ifNil:[
                    Stderr
                        nextPutLine:'No class for report named ' , reportName;
                        nextPutLine:'Ignoring'
                ]
                ifNotNil:[reports add:(report := report new)].
            "Check for format"
            i := argv indexOf:'-F' startingAt:i.
            i ~~ 0 ifTrue:[
                formatName := argv at:i + 1.
                i := i + 2.
                report format: formatName asSymbol.
            ].
        ].
        i := 1.
        [
            i := argv indexOf:'-p' startingAt:i.
            i ~~ 0 and:[i < argc]
        ] whileTrue:[
            |pkg|

            pkg := argv at:i + 1.
            i := i + 2.
            reports do:[:report |
                                self verboseInfo: 
                                        ('Running %1 for package %2' bindWith: report name with: pkg).
                report runPackage:pkg
            ]
        ].
        Smalltalk isStandAloneApp ifTrue:[
            Smalltalk exit:0.
        ]
    ] on:Error
            do:[:ex | 
        Stderr nextPutAll:'Error when running tests: '.
        Stderr
            nextPutAll:ex description;
            cr.
        ex suspendedContext printAllOn:Stderr.
        Smalltalk isHeadless ifTrue:[
            Smalltalk exit:1.
        ] ifFalse:[
            ex pass
        ]
    ]

    "Modified: / 06-10-2011 / 23:33:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 06-11-2011 / 21:53:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ReportRunner class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '§Id: Builder__ReportRunner.st 289 2011-11-10 15:39:10Z vranyj1 §'
! !

ReportRunner initialize!