STXInstaller.st
author Claus Gittinger <cg@exept.de>
Mon, 20 Jul 1998 13:18:24 +0200
changeset 896 0e732b716759
parent 793 43a9a195b0f3
child 1010 d744cc925443
permissions -rw-r--r--
use #copyReplaceAll:with:

Object subclass:#STXInstaller
	instanceVariableNames:'stxLibDir stxLibBinDir stxBinDir installDocFiles
		installSourceFiles installSTCFiles installGoodyFiles fullDir
		actionPercentageHolder actionTextHolder commandTraceView
		resources fullInstallation dfHolder copyProcess'
	classVariableNames:'LastBinDir LastLibBinDir LastLibDir LastFullDir'
	poolDictionaries:''
	category:'eXept-tools'
!


!STXInstaller class methodsFor:'startup'!

open
    ^ self new open

    "
     STXInstaller open
    "
! !

!STXInstaller methodsFor:'defaults'!

defaultBinDirs
    |dirs|

    dirs := OrderedCollection new.
    dirs add:'/usr/local/bin'.
    dirs add:'/usr/bin'.
    dirs add:(Filename homeDirectory constructString:'bin').
    dirs add:((Filename homeDirectory 
			    construct:'stx')
			    constructString:'bin').
    dirs add:'/tmp/stxbin'.
    ('/home' asFilename exists and:['/home' asFilename isDirectory]) ifTrue:[
        dirs add:'/home/stx/bin'.
    ].
    ('/home2' asFilename exists and:['/home2' asFilename isDirectory]) ifTrue:[
        dirs add:'/home2/stx/bin'.
    ].

"/    dirs := dirs select:[:path | 
"/                            |f|
"/
"/                            f := path asFilename.
"/                            f exists and:[f isDirectory]].
    ^ dirs sort

    "Created: 18.7.1996 / 19:43:00 / cg"
    "Modified: 18.7.1996 / 19:45:08 / cg"
!

defaultFullDirs
    |dirs|

    dirs := OrderedCollection new.
    dirs add:(Filename homeDirectory constructString:'stxDevelop').
    dirs add:((Filename homeDirectory 
                            construct:'stx')
                            constructString:'develop').
    ('/home' asFilename exists and:['/home' asFilename isDirectory]) ifTrue:[
        dirs add:'/home/stx/develop'.
    ].

    ^ dirs sort

    "Modified: / 18.7.1996 / 19:45:08 / cg"
    "Created: / 25.2.1998 / 17:14:43 / cg"
!

defaultLibBinDirs
    |dirs|

    dirs := OrderedCollection new.
    dirs add:'/usr/local/lib'.
    dirs add:'/usr/lib'.
    dirs add:'/lib'.
    dirs add:(Filename homeDirectory 
                            constructString:'lib').

    dirs add:((Filename homeDirectory 
                            construct:'stx')
                            constructString:'lib').
    dirs add:'/tmp/stxlib'.
    dirs add:'/home/stx/lib'.
    dirs add:'/home2/stx/lib'.

    ^ dirs sort

    "Created: 18.7.1996 / 19:43:21 / cg"
    "Modified: 18.7.1996 / 19:46:04 / cg"
!

defaultLibDirs
    |dirs|

    dirs := OrderedCollection new.
    dirs add:'/usr/local/lib/smalltalk'.
    dirs add:'/usr/lib/smalltalk'.
    dirs add:((Filename homeDirectory 
                            construct:'lib')
                            constructString:'smalltalk').
    dirs add:((Filename homeDirectory 
                            construct:'stx')
                            constructString:'lib').
    dirs add:'/tmp/stxlib'.
    dirs add:'/home/stx/lib'.
    dirs add:'/home2/stx/lib'.

"/    dirs := dirs select:[:path | 
"/                            |f|
"/
"/                            f := path asFilename.
"/                            f exists and:[f isDirectory]].
    ^ dirs sort

    "Created: 18.7.1996 / 19:43:21 / cg"
    "Modified: 18.7.1996 / 19:46:04 / cg"
!

directoriesToMake
    |dirsToMake|

    dirsToMake := OrderedCollection new.
    fullInstallation ifTrue:[
        dirsToMake add:fullDir.
    ] ifFalse:[
        dirsToMake add:stxBinDir.
        dirsToMake add:stxLibDir.
        dirsToMake add:stxLibBinDir.
        dirsToMake add:(stxLibDir asFilename constructString:'configurations').
        dirsToMake add:(stxLibDir asFilename constructString:'doc').
        dirsToMake add:(stxLibDir asFilename constructString:'doc/online').
        dirsToMake add:(stxLibDir asFilename constructString:'doc/online/english').
        dirsToMake add:(stxLibDir asFilename constructString:'doc/online/german').
        dirsToMake add:(stxLibDir asFilename constructString:'doc/online/french').
        dirsToMake add:(stxLibDir asFilename constructString:'doc/online/italian').
        dirsToMake add:(stxLibDir asFilename constructString:'include').
        dirsToMake add:(stxLibDir asFilename constructString:'resources').
        dirsToMake add:(stxLibDir asFilename constructString:'binary').
        dirsToMake add:(stxLibDir asFilename constructString:'bitmaps').
        dirsToMake add:(stxLibDir asFilename constructString:'goodies').
    ].
    ^ dirsToMake

    "Modified: / 25.2.1998 / 17:15:19 / cg"
!

listOfOptionalPackages
    ^ #(
        'libDB'
        'clients/CBrowser'
        'libcompat'
        'libxt'


        "/ mhmh - these should not be needed here ...

        'projects/smalltalk/bitmaps/javaImages'
        'doc/online/english/overview/icons'
      )

    "Created: 2.3.1997 / 12:39:59 / cg"
    "Modified: 2.3.1997 / 13:24:41 / cg"
!

specOfFilesToCopy
    |fileSpec|

    fileSpec := #(
                "/ name                             destination  subDir             required mode      
                ( 'projects/smalltalk/smalltalk'        #bin     nil                  true  '755' )
                ( 'projects/smalltalk/stx'              #bin     nil                  true  '755' )
                ( 'projects/smalltalk/include'          #lib     nil                  true  '644' )
                ( 'COPYRIGHT'                           #lib     nil                  true  '644' )
                ( 'projects/smalltalk/*.rc'             #lib     nil                  true  '644' )
                ( 'projects/smalltalk/patches'          #lib     nil                  true  '644' )
                ( 'projects/smalltalk/bitmaps'          #lib     nil                  true  '644' )
                ( 'projects/smalltalk/resources'        #lib     nil                  true  '644' )
                ( 'projects/smalltalk/lib'              #lib     nil                  true  '644' )
                ( 'doc/online/german/LICENCE.STX.html'  #lib     'doc/online/german'  true  '644' )
                ( 'doc/online/english/LICENCE.STX.html' #lib     'doc/online/english' true  '644' )
    ).

    installDocFiles ifTrue:[
        fileSpec := fileSpec , #(
                ( 'doc'                                  #lib     nil        false '644' )
        ).
    ].

    installSourceFiles ifTrue:[
        fileSpec := fileSpec , #(
                ( 'projects/smalltalk/source'                #lib        nil        false '644' )
        ).
    ].

    installSTCFiles ifTrue:[
        fileSpec := fileSpec , #(
                ( 'stc/stc'                                  #bin        nil              false '755' )
                ( 'rules/stmkmp'                             #bin        nil              false '755' )
                ( 'rules/stmkmf'                             #bin        nil              false '755' )
                ( 'include'                                  #lib        nil              false '644' )
                ( 'configurations'                           #lib        nil              false '644' )
                ( 'configurations/PACKS'                     #lib        'configurations' false '644' )
                ( 'configurations/my*'                       #lib        'configurations' false '644' )
                ( 'configurations/vendor*'                   #lib        'configurations' false '644' )
                ( 'rules'                                    #lib        nil              false '644' )

                ( 'support/VGL/vogl/src/libvogl.*'           #lib        'lib'            false '644' )
                ( 'support/VGL/vogl/src/*.h'                 #lib        'include'        false '644' )
                ( 'support/DLD/dld-3.2.5/libdld.*'           #lib        'lib'            false '644' )

                ( 'goodies/persistency/db-1.6/PORT/libdb.*'  #lib        'lib'            false '644' )

                ( 'librun/librun.*'                          #libBin     nil              false '644' )
                ( 'libbasic/libbasic.*'                      #libBin     nil              false '644' )
                ( 'libbasic2/libbasic2.*'                    #libBin     nil              false '644' )
                ( 'libbasic3/libbasic3.*'                    #libBin     nil              false '644' )
                ( 'libhtml/libhtml.*'                        #libBin     nil              false '644' )
                ( 'libcomp/libcomp.*'                        #libBin     nil              false '644' )
                ( 'libcomp/ObjFL*.o'                         #libBin     nil              false '644' )
                ( 'libcomp/ObjFL*.obj'                       #libBin     nil              false '644' )
                ( 'libcomp/ObjFL*.so'                        #libBin     nil              false '644' )
                ( 'libview/libview.*'                        #libBin     nil              false '644' )
                ( 'libview/GLX*.o'                           #libBin     nil              false '644' )
                ( 'libview/GLX*.obj'                         #libBin     nil              false '644' )
                ( 'libview/GLX*.so'                          #libBin     nil              false '644' )
                ( 'libview/XW*.o'                            #libBin     nil              false '644' )
                ( 'libview/XW*.obj'                          #libBin     nil              false '644' )
                ( 'libview/XW*.so'                           #libBin     nil              false '644' )
                ( 'libview2/libview2.*'                      #libBin     nil              false '644' )
                ( 'libwidg/libwidg.*'                        #libBin     nil              false '644' )
                ( 'libwidg2/libwidg2.*'                      #libBin     nil              false '644' )
                ( 'libwidg3/libwidg3.*'                      #libBin     nil              false '644' )
                ( 'libui/libui.*'                            #libBin     nil              false '644' )

"/                ( 'libsnmp/libsnmp.*'                        #libBin     nil      false '644' )
"/                ( 'contrib/libPVM/libPVM.*'                  #libBin     nil      false '644' )
                ( 'goodies/persistency/libdbase.*'           #libBin     nil      false '644' )
"/                ( 'libtable/libtable.*'                      #libBin     nil      false '644' )
                ( 'libtool/libtool.*'                        #libBin     nil      false '644' )
                ( 'libtool2/libtool2.*'                      #libBin     nil      false '644' )
"/                ( 'libxt/libxt.*'                            #libBin     nil      false '644' )
"/                ( 'librt/librt.*'                            #libBin     nil      false '644' )
        ).
    ].

    installGoodyFiles ifTrue:[
        fileSpec := fileSpec , #(
                ( 'goodies/*.st'                             #lib     'goodies'  false '644' )
                ( 'goodies/*.chg'                            #lib     'goodies'  false '644' )
                ( 'goodies/rdoit/rdoit'                      #bin     nil        false '755' )
                ( 'goodies/bitmaps/rdoit'                    #lib     'goodies/bitmaps'  false '755' )
        ).
    ].


    ^ fileSpec

    "Modified: 8.8.1997 / 18:39:06 / cg"
! !

!STXInstaller methodsFor:'installing'!

changeWritability
    |msg|

    fullInstallation ifTrue:[
        msg := (resources array:#('ST/X Installation' '' 'making target dir writable' '' '' '')) asStringCollection.

        commandTraceView showCR:(resources string:'making target dir writable ...').
        commandTraceView endEntry.
        OperatingSystem executeCommand:('(cd ' , fullDir , ' ; find . -exec chmod u+w {} \;)').
    ].

    "Created: / 17.7.1996 / 15:24:19 / cg"
    "Modified: / 20.4.1998 / 15:40:00 / cg"
!

copyFiles
    |msg fileSpec filesToCopy numFiles nDone cmd|

     msg := (resources array:#('ST/X Installation' '' 'copying:' '' 'to:' '')) asStringCollection.

    fullInstallation ifTrue:[
        msg at:4 put:('    all from CD' asText allBold).
        msg at:6 put:'    ' , (fullDir asText allBold).
        actionTextHolder value:nil.
        actionTextHolder value:msg.

        cmd := '(cd ../.. ; tar cf - .) | (cd ' , fullDir , ' ; tar xvf -)'.
"/        "/
"/        "/ not all systems have cp -rv
"/        "/
"/        OperatingSystem getOSType = 'linux' ifTrue:[
"/            cmd := 'cp -rv ../../* ' , fullDir.
"/        ].
"/      commandTraceView showCR:cmd , ' ...'.
        commandTraceView showCR:'copying ...'.
        commandTraceView endEntry.
        cmd := cmd , ' 2>&1' .

        self executeCommandAndShowOutput:cmd.

        ^ true
    ].

    fileSpec := self specOfFilesToCopy.

    filesToCopy := OrderedCollection new.

    fileSpec do:[:entry |
        |fileNames dest subDir required destDir|

        fileNames := entry at:1.
        dest := entry at:2.
        subDir := entry at:3.
        required := entry at:4.

        dest == #bin ifTrue:[
            destDir := stxBinDir
        ] ifFalse:[
            dest == #libBin ifTrue:[
                destDir := stxLibBinDir
            ] ifFalse:[
                destDir := stxLibDir
            ]
        ].
        
        destDir := destDir asFilename.
        subDir notNil ifTrue:[
            destDir := destDir construct:subDir
        ].

        filesToCopy add:(fileNames -> destDir pathName)
    ].

    numFiles := filesToCopy size.
    nDone := 0.

    filesToCopy do:[:entry |
        |fileName destDir cmd|

        fileName := entry key.
        destDir := entry value.

        ((fileName includes:$*)
        or:[('../../' , fileName) asFilename exists])ifTrue:[
            actionPercentageHolder value:(nDone / numFiles * 100) rounded.

            msg at:4 put:'    ' , (fileName asText allBold).
            msg at:6 put:'    ' , (destDir asText allBold).
            actionTextHolder value:nil.
            actionTextHolder value:msg.

            ((fileName includes:$*) not
            and:[('../../' , fileName) asFilename exists not]) ifTrue:[
                (self listOfOptionalPackages includes:fileName) ifFalse:[
                    commandTraceView showCR:('cannot copy ' , fileName , ' - not included in distribution').
                    commandTraceView endEntry.
                ]
            ] ifFalse:[
                cmd := 'cp -r ../../' , fileName , ' ' , destDir.
                commandTraceView showCR:cmd , ' ...'.
                commandTraceView endEntry.
                cmd := cmd , ' 2>&1' .

                self executeCommandAndShowOutput:cmd
            ]
        ].

        nDone := nDone + 1
    ].

    ^ true

    "
     STXInstaller open
    "

    "Created: / 17.7.1996 / 15:16:20 / cg"
    "Modified: / 20.4.1998 / 17:41:45 / cg"
!

createDirectories
    |msg dirsToMake numDirs nDone|

    msg := (resources array:#('ST/X Installation' '' 'creating directory:' '' '' '')) asStringCollection.

    dirsToMake := self directoriesToMake.

    numDirs := dirsToMake size.
    nDone := 0.

    dirsToMake do:[:dirName |
        |d errMsg stop box|

        actionPercentageHolder value:(nDone / numDirs * 100) rounded.

        msg at:4 put:'    ' , (dirName asText allBold).
        actionTextHolder value:nil.
        actionTextHolder value:msg.

        d := dirName asFilename.

        commandTraceView showCR:(resources string:'creating %1 ...' with:d pathName).
        commandTraceView endEntry.

        d exists ifFalse:[
            OperatingSystem recursiveCreateDirectory:d pathName
        ].

        d exists ifFalse:[
            errMsg := resources string:'failed to create directory: %1' with: dirName.
            stop := true
        ] ifTrue:[
            d isDirectory ifFalse:[
                errMsg := resources string:'not a directory: %1' with:dirName.
                stop := true
            ] ifTrue:[
                (d isReadable
                and:[d isWritable]) ifFalse:[
                    errMsg := resources string:'no read/write access to directory: %1' with:dirName.
                    stop := false
                ] ifTrue:[
                    errMsg := nil
                ]
            ]
        ].

        errMsg notNil ifTrue:[
            box := WarningBox new.
            box title:errMsg.
            box showAtPointerNotCovering:(WindowGroup activeGroup topViews first).
            stop ifTrue:[^ false].
        ].

        Delay waitForSeconds:0.25.
        nDone := nDone + 1.
    ].
    ^ true

    "Created: 17.7.1996 / 15:24:19 / cg"
    "Modified: 22.5.1997 / 15:06:41 / cg"
!

createSymbolicLinks
    |msg dirsToMake numDirs nDone|

    msg := (resources array:#('ST/X Installation' '' 'creating symbolic links' '' '' '')) asStringCollection.

    commandTraceView showCR:(resources string:'setting up symbolic links in doc/online ...').
    commandTraceView endEntry.
    fullInstallation ifTrue:[
        OperatingSystem executeCommand:('(cd ' , fullDir , '/doc/online ; make links)').
    ] ifFalse:[
        OperatingSystem executeCommand:('(cd ' , stxLibDir , '/doc/online ; make links)').
    ].

    "Created: / 17.7.1996 / 15:24:19 / cg"
    "Modified: / 20.4.1998 / 15:40:11 / cg"
!

executeCommandAndShowOutput:cmd
    |doneSemaphore line p|

    doneSemaphore := Semaphore new.

    copyProcess := [   

        p := PipeStream readingFrom:cmd.
        p isNil ifTrue:[
            self warn:('command error. Could not execute:\\' , cmd) withCRs.
        ] ifFalse:[
            [
                [p atEnd] whileFalse:[
                    (p readWaitWithTimeout:0.1) ifFalse:[
                        line := p nextLine.
                        (line notNil and:[line notEmpty]) ifTrue:[
                            commandTraceView showCR:(('  ' , line) asText emphasizeAllWith:(#color->Color red)).
                            commandTraceView endEntry.
                        ]
                    ]
                ].
                p close.
            ] valueOnUnwindDo:[
                p shutDown
            ]
        ].
        doneSemaphore signal.
        copyProcess := nil.
    ] forkAt:4.

    doneSemaphore wait.

    "Created: / 25.2.1998 / 17:46:06 / cg"
    "Modified: / 25.2.1998 / 18:36:50 / cg"
!

outputInitialMessage
    #(
    'Notice:'
    ''
    'During the installation, you may get error messages'
    'complaining that some files where not found'
    'and could therefore not be copied.'
    ) do:[:line |
        commandTraceView showCR:((resources string:line) asText emphasizeAllWith:(#color->Color blue)).
        commandTraceView endEntry. 
    ].

    Delay waitForSeconds:2.

    #(
    ''
    'This is normal behavior; since the CD may contain'
    'broken symbolic links to non-existing packages'
    'which are either not contained on your ordered'
    'package (i.e. non-commercial) or are not required'
    'for your architecture (and therefore not contained'
    'on the CD).'
    ''
    ) do:[:line |
        commandTraceView showCR:((resources string:line) asText emphasizeAllWith:(#color->Color blue)).
        commandTraceView endEntry.
    ].

    Delay waitForSeconds:2.

    #(
    ''
    'Please excuse this inconvenience.'
    ''
    ) do:[:line |
        commandTraceView showCR:((resources string:line) asText emphasizeAllWith:(#color->Color blue)).
        commandTraceView endEntry.
    ].

    Delay waitForSeconds:2.

    "Created: 2.3.1997 / 12:49:52 / cg"
    "Modified: 8.8.1997 / 17:47:06 / cg"
! !

!STXInstaller methodsFor:'startup'!

askAndInstall
    "/ check, if we are in the projects/smalltalk directory

    |answer|

    resources := ResourcePack for:self class.

    (Filename currentDirectory pathName endsWith:'projects/smalltalk') ifFalse:[
        self warn:(resources string:'must be in the ''projects/smalltalk'' directory').
        ^ self
    ].

    answer := self askForFullInstallation.
    answer ifFalse:[^ self].

    [self askForDestination] whileTrue:[
        self checkForExistingInstallationAndConfirm ifTrue:[
            self preInstall.
            self doInstall ifTrue:[
                self postInstall.
                ^ self
            ].
            (self confirm:(resources string:'installation failed or aborted - retry ?'))
            ifFalse:[
                ^ self
            ]
        ]
    ].

    "Modified: / 25.2.1998 / 16:54:51 / cg"
!

askForDestination
    "open a dialog to enter destination directories"

    fullInstallation ifTrue:[
        ^ self askForDestinationForFullInstallation
    ] ifFalse:[
        ^ self askForDestinationForPartialInstallation
    ]

    "
     STXInstaller open
    "

    "Modified: / 25.2.1998 / 17:12:45 / cg"
!

askForDestinationForFullInstallation
    "open a dialog to enter destination directories"

    |d cm l green dark img
     fullDirHolder|

    LastFullDir isNil ifTrue:[
        LastFullDir := (Filename homeDirectory 
                            construct:'stx')
                            constructString:'develop'
    ].

    fullDirHolder := LastFullDir asValue.

    Screen current hasColors ifTrue:[
        green := (Color red:0 green:80 blue:20) "darkened".
        dark := Color grey:10.
    ] ifFalse:[
        green := Color white.
        dark := Color black.
    ].

    d := DialogBox new.

    d label:(resources string:'ST/X Full Installation').
    img := Image fromFile:'SmalltalkX.xbm'.

    l := d addTextLabel:img.
    l adjust:#left; foregroundColor:green backgroundColor:dark.

    l := d addTextLabel:(resources string:'Smalltalk/X CD installation (full).').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
    d addVerticalSpace.
    d addVerticalSpace.

    d addHorizontalLine.

    l := d addTextLabel:(resources string:'ST/X development directory:').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.

    cm := ComboBoxView on:fullDirHolder.
    cm list:self defaultFullDirs.
    d 
        addLabelledField:cm 
        label:(resources string:'stx develop')
        adjust:#left 
        tabable:true 
        from:0.0 to:1.0 separateAtX:0.25
        nameAs:'fullBox'.

    (d componentAt:'fullBox.label') backgroundColor:dark; foregroundColor:Color white.

    d addVerticalSpace.
    d addHorizontalLine.

    d addHelpButtonFor:'STXInstaller/installHelp.html';
      addAbortButton; 
      addOkButtonLabelled:(resources string:'install').
    d extent:500@400.

    d allViewBackground:dark.

    d openAtCenter.
    d accepted ifTrue:[
        fullDir := LastFullDir := fullDirHolder value.
        d destroy.
        ^ true
    ].
    d destroy.
    ^ false

    "
     STXInstaller open
    "

    "Created: / 25.2.1998 / 17:11:37 / cg"
    "Modified: / 25.2.1998 / 17:29:07 / cg"
!

askForDestinationForPartialInstallation
    "open a dialog to enter destination directories"

    |d cm l green dark img
     stxLibDirHolder stxLibBinDirHolder stxBinDirHolder
     installDocHolder installSourceHolder installSTCHolder installGoodiesHolder
     binMegabytes libMegabytes docMegabytes stcMegabytes srcMegabytes
    |

    binMegabytes := 12.
    libMegabytes := 30.
    docMegabytes := 15.
    stcMegabytes := 1.
    srcMegabytes := 20.

    LastLibDir isNil ifTrue:[
        LastLibDir := '/usr/local/lib/smalltalk'
    ].
    LastLibBinDir isNil ifTrue:[
        LastLibBinDir := '/usr/local/lib'
    ].
    LastBinDir isNil ifTrue:[
        LastBinDir := '/usr/local/bin'
    ].

    stxLibDirHolder := LastLibDir asValue.
    stxLibBinDirHolder := LastLibBinDir asValue.
    stxBinDirHolder := LastBinDir asValue.

    installDocHolder := true asValue.
    installSourceHolder := true asValue.
    installSTCHolder := true asValue.
    installGoodiesHolder := true asValue.

    Screen current hasColors ifTrue:[
        green := (Color red:0 green:80 blue:20) "darkened".
        dark := Color grey:10.
    ] ifFalse:[
        green := Color white.
        dark := Color black.
    ].

    d := DialogBox new.

    d label:(resources string:'ST/X Partial Installation').
    img := Image fromFile:'SmalltalkX.xbm'.

    l := d addTextLabel:img.
    l adjust:#left; foregroundColor:green backgroundColor:dark.

    l := d addTextLabel:(resources string:'Smalltalk/X CD installation (partial).').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
    d addVerticalSpace.
    d addVerticalSpace.

    d addHorizontalLine.

    l := d addTextLabel:(resources string:'Destination directories:').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.

    l := d addTextLabel:(resources string:'(the defaults below are recommended)').
    l adjust:#right; backgroundColor:dark; foregroundColor:Color white.

    cm := ComboBoxView on:stxBinDirHolder.
    cm list:self defaultBinDirs.
    d 
        addLabelledField:cm 
        label:(resources string:'binaries')
        adjust:#left 
        tabable:true 
        from:0.0 to:1.0 separateAtX:0.25
        nameAs:'binaryBox'.

    (d componentAt:'binaryBox.label') backgroundColor:dark; foregroundColor:Color white.

    cm := ComboBoxView on:stxLibBinDirHolder.
    cm list:self defaultLibBinDirs.
    d 
        addLabelledField:cm 
        label:(resources string:'libraries') 
        adjust:#left 
        tabable:true 
        from:0.0 to:1.0 separateAtX:0.25
        nameAs:'libraryBinBox'.

    (d componentAt:'libraryBinBox.label') backgroundColor:dark; foregroundColor:Color white.

    cm := ComboBoxView on:stxLibDirHolder.
    cm list:self defaultLibDirs.
    d 
        addLabelledField:cm 
        label:(resources string:'other files') 
        adjust:#left 
        tabable:true 
        from:0.0 to:1.0 separateAtX:0.25
        nameAs:'libraryBox'.

    (d componentAt:'libraryBox.label') backgroundColor:dark; foregroundColor:Color white.

    d addVerticalSpace.
    d addHorizontalLine.
    d addVerticalSpace.

    (d addTextLabel:(resources string:'required:'))
        adjust:#left; foregroundColor:Color white backgroundColor:dark.

    d leftIndent:35.
    (d addTextLabel:(resources string:'binaries (approx. %1 Mb)' with:binMegabytes printString))
        adjust:#left; foregroundColor:Color white backgroundColor:dark.
    (d addTextLabel:(resources string:'libraries (approx. %1 Mb)' with:libMegabytes printString))
        adjust:#left; foregroundColor:Color white backgroundColor:dark.
    d leftIndent:0.

    d addVerticalSpace.
    d addHorizontalLine.
    d addVerticalSpace.

    (d addTextLabel:(resources string:'optional:'))
        adjust:#left; foregroundColor:Color white backgroundColor:dark.

    (d addCheckBox:((resources string:'doc files (+%1 Mb)' with:docMegabytes)) on:installDocHolder)
        labelView foregroundColor:Color white backgroundColor:dark.
    (d addCheckBox:((resources string:'stc & support files (+%1 Mb)' with:stcMegabytes)) on:installSTCHolder)
        labelView foregroundColor:Color white backgroundColor:dark.

    d addVerticalSpace.
    d addHorizontalLine.
    d addVerticalSpace.

    (d addTextLabel:(resources string:'optional (but highly recommended):'))
        adjust:#left; foregroundColor:Color white backgroundColor:dark.

    (d addCheckBox:((resources string:'smalltalk source files (+%1 Mb)' with:srcMegabytes)) on:installSourceHolder)
        labelView foregroundColor:Color white backgroundColor:dark.
    (d addCheckBox:((resources string:'goodies (+0.5 Mb)')) on:installGoodiesHolder)
        labelView foregroundColor:Color white backgroundColor:dark.

    d addVerticalSpace.
    d addHorizontalLine.

    d addHelpButtonFor:'STXInstaller/installHelp.html';
      addAbortButton; 
      addOkButtonLabelled:(resources string:'install').
    d extent:500@400.

    d allViewBackground:dark.

    d openAtCenter.
    d accepted ifTrue:[
        stxLibDir := LastLibDir := stxLibDirHolder value.
        stxLibBinDir := LastLibBinDir := stxLibBinDirHolder value.
        stxBinDir := LastBinDir := stxBinDirHolder value.
        installDocFiles := installDocHolder value.
        installSourceFiles := installSourceHolder value.
        installSTCFiles := installSTCHolder value.
        installGoodyFiles := installGoodiesHolder value.
        d destroy.
        ^ true
    ].
    d destroy.
    ^ false

    "
     STXInstaller open
    "

    "Created: / 25.2.1998 / 17:11:26 / cg"
    "Modified: / 25.2.1998 / 19:43:30 / cg"
!

askForFullInstallation
    "open a dialog to enter destination directories"

    |d cm l green dark img|

    Screen current hasColors ifTrue:[
        green := (Color red:0 green:80 blue:20) "darkened".
        dark := Color grey:10.
    ] ifFalse:[
        green := Color white.
        dark := Color black.
    ].

    d := DialogBox new.

    d label:(resources string:'ST/X CD Installation').
    img := Image fromFile:'SmalltalkX.xbm'.

    l := d addTextLabel:img.
    l adjust:#left; foregroundColor:green backgroundColor:dark.

    l := d addTextLabel:(resources string:'Smalltalk/X CD installation.').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
    d addVerticalSpace.
    d addVerticalSpace.

    d addHorizontalLine.

    l := d addTextLabel:(resources string:
'You can either perform a ' , 'full' asText allBold , ' installation, or a ' , 'partial' asText allBold ,' installation.').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.

    d addVerticalSpace.
    d addHorizontalLine.

    d leftIndent:20.
    l := d addTextLabel:(resources string:
'The full installation is required if you want to build your own
customized smalltalk executable. It allows you to include additional 
precompiled classes or classLibraries. 
This is also required if you want to link your own standalone executables.

It consists of a directory hierachy, including makefiles for a customizeable 
rebuild of the whole smalltalk system.
(Actually, it simply copies the whole CD contents onto your disk).
This requires roughly 120-200Mb of hard disk space.').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.

    d addVerticalSpace.
    d addHorizontalLine.

    l := d addTextLabel:(resources string:
'The partial installation requires less disk space and only copies the
smalltalk executable, shared libraries and support files onto your hard disk.
This requires roughly 70-90Mb of hard disk space.


 ').
    l adjust:#left; backgroundColor:dark; foregroundColor:Color white.


    d leftIndent:0.
    d addVerticalSpace.
    d addHorizontalLine.


    d addHelpButtonFor:'STXInstaller/installHelp.html';
      addAbortButton; 
      addOkButton:(Button label:(resources string:'install full') action:[fullInstallation:=true]);
      addOkButtonLabelled:(resources string:'install partial').
    d extent:500@400.

    d allViewBackground:dark.

    fullInstallation := false.
    d openAtCenter.
    d accepted ifTrue:[
        d destroy.
        ^ true
    ].
    d destroy.
    ^ false

    "
     STXInstaller open
    "

    "Created: / 25.2.1998 / 16:50:16 / cg"
    "Modified: / 25.2.1998 / 19:42:31 / cg"
!

checkForExistingInstallationAndConfirm
    "look if there is another installation and confirm
     reinstalling; return true if ok, false if not"

    |whichDir canOverWrite whatToDo box|

    fullInstallation ifTrue:[
        whichDir := fullDir.
        canOverWrite := false.
    ] ifFalse:[
        whichDir := stxLibDir.
        canOverWrite := true.
    ].

    whichDir asFilename exists ifTrue:[
            whatToDo := Dialog 
                            choose:(resources 
                                        string:'detected existing ST/X installation in %1' 
                                          with:whichDir asText allBold)
                            label:(resources string:'Attention')
                            labels:(resources array:(canOverWrite 
                                                    ifFalse:[#('remove first' 'cancel')] 
                                                    ifTrue:[#('remove first' 'overwrite' 'cancel')] )) 
                            values:(canOverWrite ifFalse:[#(remove nil)] ifTrue:[#(remove over nil)])
                            default:nil.     

            whatToDo isNil ifTrue:[^false].
            whatToDo == #remove ifTrue:[
                ((whichDir findString:'stx') == 0
                and:[(whichDir findString:'smalltalk') == 0]) ifTrue:[
                    "/ confirm again
                    (self confirm:(resources 
                                    string:'are you certain that the directory to remove
(' , whichDir , ') is really a smalltalk directory ?

Remove it now ?')) ifFalse:[ 
                        ^ false
                    ]
                ].

                [
                    box := DialogBox new label:'please wait'.
                    box addTextLabel:'removing ' , whichDir , ' ...'.
                    box showAtPointer.
                ] forkAt:(Processor activePriority+1).
                box waitUntilVisible.

                (OperatingSystem recursiveRemoveDirectory:whichDir)
                ifFalse:[
                    self warn:(resources string:'mhmh - could not remove old installation.

Please remove it manually (using root privileges if required) 
and try again.').
                    box destroy.
                    ^ false
                ].

                box destroy
            ].
    ].

    ^ true

    "
     STXInstaller open
    "

    "Modified: / 25.2.1998 / 19:35:12 / cg"
!

doInstall
    "install ST/X; return true if ok, false if not"

    |progressView ok v textView p l 
     dirToMonitor doDfMonitoring dfMonitorProcess|

    doDfMonitoring := false.

    v := View new preferredExtent:(250 @ 350).

    textView := HVScrollableView for:TextCollector in:v.
    textView origin:0.0@0.0 corner:1.0@1.0.
    textView bottomInset:30.
    commandTraceView := textView scrolledView.

    fullInstallation ifTrue:[
        dirToMonitor := fullDir.
    ] ifFalse:[
        dirToMonitor := stxLibDir
    ].

    (OperatingSystem canExecuteCommand:'df ' , dirToMonitor) ifTrue:[
        p := HorizontalPanelView in:v.
        p origin:0.0@1.0 corner:1.0@1.0.
        p topInset:-30.
        p horizontalLayout:#fit.

        l := Label label:'' in:p.
        l labelChannel:(dfHolder := '' asValue).
        l adjust:#left.
        dfMonitorProcess := [
            |ok p text keys values i l|

            ok := true.
            [ok] whileTrue:[
                doDfMonitoring ifTrue:[
                    ok := false.
                    p := PipeStream readingFrom:('df -k ' , dirToMonitor).
                    p notNil ifTrue:[
                       [
                           text := p contentsOfEntireFile.
                       ] valueNowOrOnUnwindDo:[
                           p close.
                       ].
"/ Transcript showCR:text asString.
                       text notNil ifTrue:[
                           text := text asCollectionOfLines.
                           text size >= 2 ifTrue:[
                               keys := (text at:1) asCollectionOfWords.
                               values := (text at:2) asCollectionOfWords.
                               i := (keys indexOf:'Capacity').
                               i == 0 ifTrue:[
                                   i := (keys indexOf:'capacity').
                               ].
                               i ~~ 0 ifTrue:[
                                   l := 'Used disk space: ' , (values at:i) withoutSeparators.
                                   i := (keys indexOf:'Available').
                                   i == 0 ifTrue:[
                                       i := (keys indexOf:'available').
                                       i == 0 ifTrue:[
                                           i := (keys indexOf:'avail').
                                           i == 0 ifTrue:[
                                               i := (keys indexOf:'Avail').
                                           ].
                                       ].
                                   ].
                                   i ~~ 0 ifTrue:[
                                        l := l , ' (' , (values at:i) withoutSeparators , 'k available)'.
                                   ].
                                   dfHolder value:l.
                                   ok := true.
                                   Delay waitForSeconds:9.
                               ]
                           ]
                        ].
                    ].
                ].
                Delay waitForSeconds:1.
            ]
        ] forkAt:(Processor activePriority+3)
    ].

    progressView := ProgressIndicator
                        inBoxWithLabel:'ST/X Installation' icon:(Depth8Image fromImage:Launcher aboutIcon)
                        text:#('ST/X Installation' '' '' '' '' '' '' '') asStringCollection
                        abortable:true
                        view:v
                        closeWhenDone:false.
    progressView topView extent:(640 min:Display width) @ (500 min:Display height).

    ok := false.

    progressView showProgressOf:
            [:progressValue :currentAction| |msg|

              Processor activeProcess withPriority:7 do:[
                  [
                      actionPercentageHolder := progressValue.
                      actionTextHolder := currentAction.

                      fullInstallation ifFalse:[
                            self outputInitialMessage.
                      ].

                      (self createDirectories) ifTrue:[
                          doDfMonitoring := true.
                          ok := self copyFiles
                      ].
                      self changeWritability.
                      self createSymbolicLinks.

                      progressValue value:100.

                      progressView topView abortButton label:(resources string:'continue').
                      progressView topView abortButton action:[progressView topView hide].
                      msg := (resources 
                                 array:#('ST/X Installation finished.' '' 'press continue ...' '' '' ''))
                                     asStringCollection.
                      actionTextHolder value:nil.
                      actionTextHolder value:msg.
                 ] valueOnUnwindDo:[
                    dfMonitorProcess notNil ifTrue:[
                        dfMonitorProcess terminate.
                        dfMonitorProcess := nil.
                    ].
                    copyProcess notNil ifTrue:[
                        copyProcess terminate.
                        copyProcess := nil.
                    ].
                 ]
              ] 
            ].

    dfMonitorProcess notNil ifTrue:[
        dfMonitorProcess terminate.
        dfMonitorProcess := nil.
    ].
    copyProcess notNil ifTrue:[
        copyProcess terminate.
        copyProcess := nil.
    ].
    ^ ok

    "
     STXInstaller open
    "

    "Created: / 17.7.1996 / 15:11:27 / cg"
    "Modified: / 20.4.1998 / 15:36:40 / cg"
!

open
    self askAndInstall.

    "
     STXInstaller open
    "
!

postInstall
    "some messages at the end ..."

    |shInfo cshInfo msg havePath|

    resources isNil ifTrue:[
        resources := ResourcePack for:self class.
    ].

    msg := (resources string:'ST/X Installation complete.\\') withCRs.
    shInfo := ''.
    cshInfo := ''.

    fullInstallation ifTrue:[
        msg := msg , 'You will now find a development directory hierarchy
in ''' , fullDir asText allBold , '''.

To try it, ''cd'' to ''' , fullDir , '/projects/smalltalk''
and start smalltalk with the command: ''./smalltalk''.

To perform a partial installation of your customized smalltalk later,
use the INSTALL script found in ''' , fullDir , ''''.

    ] ifFalse:[
        havePath := true.
        (((OperatingSystem getEnvironment:'PATH')
            asCollectionOfSubstringsSeparatedBy:$:)
                includes:stxBinDir) ifFalse:[

            havePath := false.
            shInfo  := 'PATH=$PATH:' , stxBinDir , ' ; export PATH\'.
            cshInfo := 'set path=($path ' , stxBinDir , ')\'.
            msg := msg , (resources string:'%1 is not in your PATH.\You should change your ".login" and/or ".profile" files to include it.\\'
                                      with:stxBinDir asText allBold) withCRs.
        ].

        (stxLibDir ~= '/usr/local/lib/smalltalk'
        and:[stxLibDir ~= '/usr/lib/smalltalk']) ifTrue:[
            msg := msg , (resources string:'The library directory is not a standard ST/X library directory\("/usr/local/lib/smalltalk" or "/usr/lib/smalltalk").\You have to define the %1 environment variable\as %2 before ST/X can be started.\'
                                      with:'STX_LIBDIR' asText allBold 
                                      with:stxLibDir asText allBold) withCRs.
            havePath ifFalse:[
                msg := msg , (resources string:'The above mentioned files are also a good place to do this.\') withCRs.
            ] ifTrue:[
                msg := msg , (resources string:'The ".login" and/or ".profile" files are a good place to do this.\') withCRs.
            ].

            shInfo := shInfo , 'STX_LIBDIR=' , stxLibDir , ' ; export STX_LIBDIR\'.
            cshInfo := cshInfo , 'setenv STX_LIBDIR ' , stxLibDir , '\'.
        ].

        shInfo notEmpty ifTrue:[
            '*********************************************************' errorPrintCR.
            (resources string:'Message from the ST/X Installer:\\') withCRs errorPrintCR.
            (resources string:'Please add the following to your ".profile" file:') withCRs errorPrintCR.
            '' errorPrintCR.
            shInfo withCRs errorPrintCR.
            '' errorPrintCR.
            (resources string:'or (if you use csh/tcsh), add to your ".login" file:') withCRs errorPrintCR.
            '' errorPrintCR.
            cshInfo withCRs errorPrintCR.
            '' errorPrintCR.
            '*********************************************************' errorPrintCR.
        ].
    ].

    msg := msg , '\\Have fun using ST/X !!'.

    self information:msg withCRs.

    "Modified: / 25.2.1998 / 19:29:04 / cg"
!

preInstall
    "clobber the doc directory, to avoid copying cyclic symbolic links.
     Notice, the CD does not contain symlinks, but checking for them
     allows installing from a development dir."

    |f|

    f := '../../doc/online/english/german' asFilename.
    f exists ifTrue:[
        f isSymbolicLink ifTrue:[
            OperatingSystem executeCommand:'(cd ../../doc/online; make clobber) >/dev/null 2>/dev/null'
        ]
    ]

    "
     STXInstaller new preInstall
    "

    "Modified: / 25.2.1998 / 17:39:55 / cg"
! !

!STXInstaller class methodsFor:'documentation'!

version
    ^ '$Header$'
! !