StandaloneStartup.st
author Claus Gittinger <cg@exept.de>
Tue, 19 Sep 2006 16:50:31 +0200
changeset 9944 aa3d787443ef
child 10040 59d0c20b139f
permissions -rw-r--r--
initial checkin

"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libbasic' }"

Object subclass:#StandaloneStartup
	instanceVariableNames:''
	classVariableNames:'Verbose'
	poolDictionaries:''
	category:'System-Support'
!

!StandaloneStartup class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    a subclassable template class for a standalone GUI-application's startup;
    For your own stand alone programs, define a subclass of this, 
    and redefine the #main method there.
    (of course, the other methods can also be redefined.)

    [author:]
        Claus Gittinger

    [start with:]
        <yourNamehere>Startup start
"
! !

!StandaloneStartup class methodsFor:'initialization'!

initialize
    "/ Verbose := true.
    Verbose := false.
! !

!StandaloneStartup class methodsFor:'helpers'!

redirectStandardStreams
    Stdout := Stderr.
    Transcript := Stderr.
!

verboseInfo:msg
    Verbose == true ifFalse:[^ self].

    Transcript 
        show:('%1 [info]: ' bindWith:(self applicationName));
        showCR:msg

    "Modified: / 19-09-2006 / 16:30:27 / cg"
! !

!StandaloneStartup class methodsFor:'queries'!

applicationName
    "used in verbose messages - can be redefined in subclasses"

    |nm|

    nm := self nameWithoutPrefix.
    (nm endsWith:'Startup') ifTrue:[
        ^ nm copyWithoutLast:('Startup' size).
    ].
    (nm endsWith:'Start') ifTrue:[
        ^ nm copyWithoutLast:('Start' size).
    ].
    ^ nm

    "Created: / 19-09-2006 / 16:26:44 / cg"
!

startupFilename
    "used in verbose messages - can be redefined in subclasses"

    ^ self applicationName asLowercase,'Start.rc'

    "
     ExpeccoStartup startupFilename
    "

    "Created: / 19-09-2006 / 16:38:28 / cg"
! !

!StandaloneStartup class methodsFor:'startup'!

loadPatches
    |patchesFile|

    patchesFile := OperatingSystem pathOfSTXExecutable asFilename directory construct:'patches'.
    (patchesFile exists and:[patchesFile isDirectory]) ifTrue:[
        patchesFile directoryContentsAsFilenamesDo:[:eachFile |
            self verboseInfo:('loading patch: ',eachFile pathName).
            Smalltalk fileIn:(eachFile pathName).
        ].
    ].

    "Modified: / 19-09-2006 / 16:30:58 / cg"
!

setupSmalltalkFromArguments:argv
    |idx rcFilename nextArg|

"/    Smalltalk beHeadless:true.
"/    OperatingSystem disableSignal:(OperatingSystem sigHUP).
"/    Smalltalk infoPrinting:true.

    (argv includes:'--help') ifTrue:[
        self usage.
        AbortOperationRequest raise.
    ].

    idx := argv indexOfAny:#('--verbose' '-V').
    idx ~~ 0 ifTrue:[
        argv removeAtIndex:idx.
        Verbose := true.
    ].
    self verboseInfo:('args: ',argv printString).

    idx := argv indexOfAny:#('--debug').
    idx ~~ 0 ifTrue:[
        argv removeAtIndex:idx.
        self setupToolsForDebug.
    ] ifFalse:[
        self setupToolsForNoDebug.
    ].

    idx := argv indexOf:'--rcFileName'.
    idx ~~ 0 ifTrue:[
        nextArg := argv at:(idx + 1) ifAbsent:nil.
        (nextArg notNil and:[ (nextArg startsWith:'-') not ]) ifTrue:[
            rcFilename := nextArg.
            argv removeAtIndex:idx+1; removeAtIndex:idx.
        ]
    ].

    rcFilename isNil ifTrue:[
        rcFilename := self startupFilename.
    ].
    rcFilename asFilename exists ifTrue:[
        self verboseInfo:('reading ',rcFilename,'...').
        rcFilename isAbsolute ifFalse:[
            rcFilename := OperatingSystem pathOfSTXExecutable asFilename directory constructString:rcFilename.
        ].
        Smalltalk secureFileIn:rcFilename
    ].
    ^ true

    "Modified: / 19-09-2006 / 16:41:00 / cg"
!

setupToolsForDebug
    Debugger := DebugView ? MiniDebugger.
    Inspector := InspectorView ? MiniInspector.
    self verboseInfo:('debug enabled - CTRL-C brings you into a debugger.').

    "Created: / 19-09-2006 / 16:40:32 / cg"
!

setupToolsForNoDebug
    Debugger := nil.
    Inspector := nil.
    NewLauncher := nil.
    self redirectStandardStreams.

    "Created: / 19-09-2006 / 16:40:47 / cg"
!

start
    self verboseInfo:('starting...').

    Smalltalk isStandAloneApp ifTrue:[
        self loadPatches.
        self verboseInfo:('setup Smalltalk').
        self setupSmalltalkFromArguments:Smalltalk commandLineArguments.
    ].
    self main

    "Modified: / 19-09-2006 / 16:34:09 / cg"
!

usage
    Stderr nextPutLine:'usage:'.
    Stderr nextPutLine:'  ',self applicationName,' [options...]'.
    Stderr nextPutLine:'    options:'.
    Stderr nextPutLine:'          --help .................. output this message'.
    Stderr nextPutLine:'          --verbose ............... verbose startup'.
    Stderr nextPutLine:'          --debug ................. enable Debugger'.
    Stderr nextPutLine:'          --rcFileName file ....... execute code from file on startup (default: ',self startupFilename,')'.

    "Created: / 19-09-2006 / 16:37:55 / cg"
! !

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

main
    |argv app fileArg|

    self verboseInfo:('entering main').

    self subclassResponsibility.

"/ a typical main looks like (in a subclass):

"/    self verboseInfo:('starting application').
"/    app := <someGUIApplicationModelClass> open.
"/
"/    argv := Smalltalk commandLineArguments.
"/    self verboseInfo:('looking for args in ',argv).
"/    argv notEmptyOrNil ifTrue:[
"/        fileArg := argv last asFilename.
"/        self verboseInfo:('fileArg is ',fileArg name).
"/        fileArg exists ifTrue:[
"/            self verboseInfo:('file exists').
"/
"/            ( #('foo' 'bar' 'baz' ) includes:fileArg suffix) ifTrue:[
"/                self verboseInfo:('loading').
"/
"/                Error handle:[:ex |
"/                    self verboseInfo:'error while loading'.
"/                    ex suspendedContext fullPrintAll.
"/                ] do:[
"/                    app menuLoadFromFile:fileArg
"/                ].
"/            ].
"/        ].
"/    ].

    "Created: / 19-09-2006 / 16:48:29 / cg"
! !

!StandaloneStartup class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/StandaloneStartup.st,v 1.1 2006-09-19 14:50:31 cg Exp $'
! !

StandaloneStartup initialize!