STXInstaller.st
changeset 1132 ef8fb42803b0
parent 1119 556bb6c9e36c
child 1133 763354d388ca
equal deleted inserted replaced
1131:4721b93b9cdc 1132:ef8fb42803b0
     1 Object subclass:#STXInstaller
     1 Object subclass:#STXInstaller
     2 	instanceVariableNames:'stxLibDir stxLibBinDir stxBinDir installDocFiles
     2 	instanceVariableNames:'stxLibDir stxLibBinDir stxBinDir installDocFiles
     3 		installSourceFiles installSTCFiles installGoodyFiles fullDir
     3 		installSourceFiles installSTCFiles installGoodyFiles fullDir
     4 		actionPercentageHolder actionTextHolder commandTraceView
     4 		actionPercentageHolder actionTextHolder commandTraceView
     5 		resources dfHolder copyProcess installWhat'
     5 		resources dfHolder copyProcess installWhat'
     6 	classVariableNames:'LastBinDir LastLibBinDir LastLibDir LastFullDir'
     6 	classVariableNames:'LastPartialDir LastBinDir LastLibBinDir LastLibDir LastFullDir'
     7 	poolDictionaries:''
     7 	poolDictionaries:''
     8 	category:'eXept-tools'
     8 	category:'eXept-tools'
     9 !
     9 !
    10 
    10 
    11 
    11 
    20 ! !
    20 ! !
    21 
    21 
    22 !STXInstaller methodsFor:'defaults'!
    22 !STXInstaller methodsFor:'defaults'!
    23 
    23 
    24 defaultBinDirs
    24 defaultBinDirs
    25     |dirs|
    25     |dirs stxRel|
    26 
    26 
       
    27     stxRel := self smalltalkRelease.
    27     dirs := OrderedCollection new.
    28     dirs := OrderedCollection new.
    28 
    29 
    29     OperatingSystem isMSWINDOWSlike ifTrue:[
    30     OperatingSystem isMSWINDOWSlike ifTrue:[
    30         dirs add:'\Programme\eXept\SmalltalkX\' , self smalltalkRelease , '\bin'.
    31         dirs add:'c:\Programme\eXept\SmalltalkX\' , stxRel , '\bin'.
    31         dirs add:'\Programme\SmalltalkX\' , self smalltalkRelease , '\bin'.
    32         dirs add:'c:\Programme\SmalltalkX\' , stxRel , '\bin'.
    32         dirs add:'\SmalltalkX\' , self smalltalkRelease , '\bin'.
    33         dirs add:'c:\SmalltalkX\' , stxRel , '\bin'.
    33     ] ifFalse:[
    34     ] ifFalse:[
    34         dirs add:'/opt/smalltalk/' , self smalltalkRelease , '/bin'.
    35         dirs add:'/opt/smalltalk/' , stxRel , '/bin'.
    35         dirs add:'/usr/local/bin'.
    36         dirs add:'/usr/local/bin'.
    36         dirs add:'/usr/bin'.
    37         dirs add:'/usr/bin'.
    37 
    38 
    38         dirs add:(Filename homeDirectory constructString:'bin').
    39         dirs add:(Filename homeDirectory constructString:'bin').
    39         dirs add:((Filename homeDirectory 
    40         dirs add:((Filename homeDirectory 
    54 "/                            f := path asFilename.
    55 "/                            f := path asFilename.
    55 "/                            f exists and:[f isDirectory]].
    56 "/                            f exists and:[f isDirectory]].
    56     ^ dirs "sort"
    57     ^ dirs "sort"
    57 
    58 
    58     "Created: / 18.7.1996 / 19:43:00 / cg"
    59     "Created: / 18.7.1996 / 19:43:00 / cg"
    59     "Modified: / 30.4.1999 / 11:56:03 / cg"
    60     "Modified: / 31.5.1999 / 12:11:48 / cg"
    60 !
    61 !
    61 
    62 
    62 defaultFullDirs
    63 defaultFullDirs
    63     |dirs|
    64     |dirs|
    64 
    65 
    76     "Modified: / 18.7.1996 / 19:45:08 / cg"
    77     "Modified: / 18.7.1996 / 19:45:08 / cg"
    77     "Created: / 25.2.1998 / 17:14:43 / cg"
    78     "Created: / 25.2.1998 / 17:14:43 / cg"
    78 !
    79 !
    79 
    80 
    80 defaultLibBinDirs
    81 defaultLibBinDirs
    81     |dirs|
    82     |dirs stxRel|
    82 
    83 
       
    84     stxRel := self smalltalkRelease.
    83     dirs := OrderedCollection new.
    85     dirs := OrderedCollection new.
    84     OperatingSystem isMSWINDOWSlike ifTrue:[
    86     OperatingSystem isMSWINDOWSlike ifTrue:[
    85         dirs add:'\Programme\eXept\SmalltalkX\' , self smalltalkRelease , '\lib'.
    87         dirs add:'c:\Programme\eXept\SmalltalkX\' , stxRel , '\lib'.
    86         dirs add:'\Programme\SmalltalkX\' , self smalltalkRelease , '\lib'.
    88         dirs add:'c:\Programme\SmalltalkX\' , stxRel , '\lib'.
    87         dirs add:'\SmalltalkX\' , self smalltalkRelease , '\lib'.
    89         dirs add:'c:\SmalltalkX\' , stxRel , '\lib'.
    88     ] ifFalse:[
    90     ] ifFalse:[
       
    91         dirs add:'/opt/smalltalk/' , stxRel , '/lib'.
    89         dirs add:'/usr/local/lib'.
    92         dirs add:'/usr/local/lib'.
    90         dirs add:'/usr/lib'.
    93         dirs add:'/usr/lib'.
    91         dirs add:'/lib'.
    94         dirs add:'/lib'.
    92         dirs add:(Filename homeDirectory 
    95         dirs add:(Filename homeDirectory 
    93                                 constructString:'lib').
    96                                 constructString:'lib').
   100         dirs add:'/home2/stx/lib'.
   103         dirs add:'/home2/stx/lib'.
   101     ].
   104     ].
   102     ^ dirs sort
   105     ^ dirs sort
   103 
   106 
   104     "Created: / 18.7.1996 / 19:43:21 / cg"
   107     "Created: / 18.7.1996 / 19:43:21 / cg"
   105     "Modified: / 30.4.1999 / 11:56:48 / cg"
   108     "Modified: / 31.5.1999 / 12:12:17 / cg"
   106 !
   109 !
   107 
   110 
   108 defaultLibDirs
   111 defaultLibDirs
   109     |dirs|
   112     |dirs stxRel|
   110 
   113 
       
   114     stxRel := self smalltalkRelease.
   111     dirs := OrderedCollection new.
   115     dirs := OrderedCollection new.
   112     OperatingSystem isMSWINDOWSlike ifTrue:[
   116     OperatingSystem isMSWINDOWSlike ifTrue:[
   113         dirs add:'\Programme\eXept\SmalltalkX\' , self smalltalkRelease , '\lib'.
   117         dirs add:'c:\Programme\eXept\SmalltalkX\' , stxRel , '\lib'.
   114         dirs add:'\Programme\SmalltalkX\' , self smalltalkRelease , '\lib'.
   118         dirs add:'c:\Programme\SmalltalkX\' , stxRel , '\lib'.
   115         dirs add:'\SmalltalkX\' , self smalltalkRelease , '\lib'.
   119         dirs add:'c:\SmalltalkX\' , stxRel , '\lib'.
   116     ] ifFalse:[
   120     ] ifFalse:[
   117         dirs add:'/opt/smalltalk/' , self smalltalkRelease , '/lib'.
   121         dirs add:'/opt/smalltalk/' , stxRel , '/lib'.
   118         dirs add:'/usr/local/lib/smalltalk'.
   122         dirs add:'/usr/local/lib/smalltalk'.
   119         dirs add:'/usr/lib/smalltalk'.
   123         dirs add:'/usr/lib/smalltalk'.
   120         dirs add:((Filename homeDirectory 
   124         dirs add:((Filename homeDirectory 
   121                                 construct:'lib')
   125                                 construct:'lib')
   122                                 constructString:'smalltalk').
   126                                 constructString:'smalltalk').
   134 "/                            f := path asFilename.
   138 "/                            f := path asFilename.
   135 "/                            f exists and:[f isDirectory]].
   139 "/                            f exists and:[f isDirectory]].
   136     ^ dirs "sort"
   140     ^ dirs "sort"
   137 
   141 
   138     "Created: / 18.7.1996 / 19:43:21 / cg"
   142     "Created: / 18.7.1996 / 19:43:21 / cg"
   139     "Modified: / 30.4.1999 / 11:57:02 / cg"
   143     "Modified: / 31.5.1999 / 12:12:30 / cg"
   140 !
   144 !
   141 
   145 
   142 directoriesToMake
   146 directoriesToMake
   143     |dirsToMake|
   147     |dirsToMake|
   144 
   148 
   300 specOfWindowsFilesToCopy
   304 specOfWindowsFilesToCopy
   301     |fileSpec|
   305     |fileSpec|
   302 
   306 
   303     fileSpec := #(
   307     fileSpec := #(
   304                 "/ name                             destination  subDir             required       
   308                 "/ name                             destination  subDir             required       
   305 "/                ( 'binbc\smalltalk'                     #bin     nil                  true   )
   309                 ( 'projects\smalltalk\smalltalk.bat'    #bin     nil                  true   )
   306                 ( 'binbc\stx'                           #bin     nil                  true   )
   310                 ( 'projects\smalltalk\stx.exe'          #bin     nil                  true   )
   307                 ( 'binbc\include'                       #lib     nil                  true   )
   311                 ( 'projects\smalltalk\stxspawn.exe'     #bin     nil                  true   )
   308                 ( 'binbc\lib*.dll'                      #bin     nil                  true   )
   312                 ( 'projects\smalltalk\include'          #lib     nil                  true   )
       
   313                 ( 'projects\smalltalk\lib*.dll'         #bin     nil                  true   )
       
   314                 ( 'projects\smalltalk\stxc3240.dll'     #bin     nil                  true   )
       
   315                 ( 'projects\smalltalk\X11.dll'          #bin     nil                  true   )
       
   316                 ( 'projects\smalltalk\Xext.dll'         #bin     nil                  true   )
       
   317                 ( 'projects\smalltalk\XWorkstat.dll'    #bin     nil                  true   )
       
   318                 ( 'projects\smalltalk\WinWorkstat.dll'  #bin     nil                  true   )
   309                 ( 'COPYRIGHT'                           #lib     nil                  true   )
   319                 ( 'COPYRIGHT'                           #lib     nil                  true   )
   310                 ( 'binbc\*.rc'                          #lib     nil                  true   )
   320                 ( 'projects\smalltalk\*.rc'             #bin     nil                  true   )
   311                 ( 'binbc\patches'                       #lib     nil                  true   )
   321                 ( 'projects\smalltalk\patches'          #bin     nil                  true   )
   312                 ( 'binbc\bitmaps'                       #lib     nil                  true   )
   322                 ( 'projects\smalltalk\bitmaps'          #lib     nil                  true   )
   313                 ( 'binbc\resources'                     #lib     nil                  true   )
   323                 ( 'projects\smalltalk\resources'        #lib     nil                  true   )
   314                 ( 'doc\online\german\LICENCE.STX.html'  #lib     'doc\online\german'  true   )
   324                 ( 'doc\online\german\LICENCE.STX.html'  #lib     'doc\online\german'  true   )
   315                 ( 'doc\online\english\LICENCE.STX.html' #lib     'doc\online\english' true   )
   325                 ( 'doc\online\english\LICENCE.STX.html' #lib     'doc\online\english' true   )
   316     ).
   326     ).
   317 
   327 
   318     installDocFiles ifTrue:[
   328     installDocFiles ifTrue:[
   319         fileSpec := fileSpec , #(
   329         fileSpec := fileSpec , #(
   320                 ( 'doc'                                  #lib     nil        false  )
   330                 ( 'doc'                                 #lib     nil        false  )
   321         ).
   331         ).
   322     ].
   332     ].
   323 
   333 
   324     installSourceFiles ifTrue:[
   334     installSourceFiles ifTrue:[
   325         fileSpec := fileSpec , #(
   335         fileSpec := fileSpec , #(
   326                 ( 'binbc\source'                         #lib     nil        false  )
   336                 ( 'projects\smalltalk\source'           #lib     nil                    false  )
       
   337                 ( 'projects\smalltalk\libbasic\*.st'    #lib     'source\libbasic'      false  )
       
   338                 ( 'projects\smalltalk\libbasic2\*.st'   #lib     'source\libbasic2'     false  )
       
   339                 ( 'projects\smalltalk\libbasic3\*.st'   #lib     'source\libbasic3'     false  )
       
   340                 ( 'projects\smalltalk\libcomp\*.st'     #lib     'source\libcomp'       false  )
       
   341                 ( 'projects\smalltalk\libview\*.st'     #lib     'source\libview'       false  )
       
   342                 ( 'projects\smalltalk\libview2\*.st'    #lib     'source\libview2'      false  )
       
   343                 ( 'projects\smalltalk\libwidg\*.st'     #lib     'source\libwidg'       false  )
       
   344                 ( 'projects\smalltalk\libwidg2\*.st'    #lib     'source\libwidg2'      false  )
       
   345                 ( 'projects\smalltalk\libwidg3\*.st'    #lib     'source\libwidg3'      false  )
       
   346                 ( 'projects\smalltalk\libtool\*.st'     #lib     'source\libtool'       false  )
       
   347                 ( 'projects\smalltalk\libtool2\*.st'    #lib     'source\libtool2'      false  )
       
   348                 ( 'projects\smalltalk\libui\*.st'       #lib     'source\libui'         false  )
       
   349                 ( 'projects\smalltalk\libhtml\*.st'     #lib     'source\libhtml'       false  )
       
   350                 ( 'projects\smalltalk\libodbc\*.st'     #lib     'source\libodbc'       false  )
       
   351                 ( 'projects\smalltalk\libopengl\*.st'   #lib     'source\libopengl'     false  )
   327         ).
   352         ).
   328     ].
   353     ].
   329 
   354 
   330     installSTCFiles ifTrue:[
   355     installSTCFiles ifTrue:[
   331         fileSpec := fileSpec , #(
   356         fileSpec := fileSpec , #(
   332                 ( 'binbc\stc'                            #bin        nil              false  )
   357                 ( 'projects\smalltalk\stc.exe'           #bin        nil              false  )
   333                 ( 'include'                              #lib        nil              false  )
   358                 ( 'include'                              #lib        nil              false  )
   334 
   359                 ( 'libbc\*.lib'                          #lib        nil              false  )
   335                 ( 'binbc\*.lib'                          #libBin     nil              false  )
       
   336         ).
   360         ).
   337     ].
   361     ].
   338 
   362 
   339     installGoodyFiles ifTrue:[
   363     installGoodyFiles ifTrue:[
   340         fileSpec := fileSpec , #(
   364         fileSpec := fileSpec , #(
   344     ].
   368     ].
   345 
   369 
   346 
   370 
   347     ^ fileSpec
   371     ^ fileSpec
   348 
   372 
   349     "Modified: / 30.4.1999 / 18:02:22 / cg"
       
   350     "Created: / 2.5.1999 / 13:23:06 / cg"
   373     "Created: / 2.5.1999 / 13:23:06 / cg"
       
   374     "Modified: / 31.5.1999 / 14:11:37 / cg"
   351 !
   375 !
   352 
   376 
   353 xxspecOfFilesToCopy
   377 xxspecOfFilesToCopy
   354     |fileSpec|
   378     |fileSpec|
   355 
   379 
   468     "Created: / 17.7.1996 / 15:24:19 / cg"
   492     "Created: / 17.7.1996 / 15:24:19 / cg"
   469     "Modified: / 20.4.1998 / 15:40:00 / cg"
   493     "Modified: / 20.4.1998 / 15:40:00 / cg"
   470 !
   494 !
   471 
   495 
   472 copyFiles
   496 copyFiles
   473     |msg fileSpec filesToCopy numFiles nDone cmd|
   497     |msg fileSpec filesToCopy numFiles nDone cmd topDir topDirPrefix|
   474 
   498 
   475      msg := (resources array:#('ST/X Installation' '' 'copying:' '' 'to:' '')) asStringCollection.
   499     msg := (resources array:#('ST/X Installation' '' 'copying:' '' 'to:' '')) asStringCollection.
       
   500 
       
   501     OperatingSystem isUNIXlike ifTrue:[
       
   502         topDir := '../..'.
       
   503         topDirPrefix := '../../'.
       
   504     ] ifFalse:[
       
   505         topDir := '..\..'.
       
   506         topDirPrefix := '..\..\'.
       
   507     ].
   476 
   508 
   477     installWhat == #full ifTrue:[
   509     installWhat == #full ifTrue:[
   478         msg at:4 put:('    all from CD' asText allBold).
   510         msg at:4 put:('    all from CD' asText allBold).
   479         msg at:6 put:'    ' , (fullDir asText allBold).
   511         msg at:6 put:'    ' , (fullDir asText allBold).
   480         actionTextHolder value:nil.
   512         actionTextHolder value:nil.
   481         actionTextHolder value:msg.
   513         actionTextHolder value:msg.
   482 
   514 
   483         cmd := '(cd ../.. ; tar cf - .) | (cd ' , fullDir , ' ; tar xvf -)'.
   515         cmd := '(cd ' , topDir , ' ; tar cf - .) | (cd ' , fullDir , ' ; tar xvf -)'.
   484 "/        "/
   516 "/        "/
   485 "/        "/ not all systems have cp -rv
   517 "/        "/ not all systems have cp -rv
   486 "/        "/
   518 "/        "/
   487 "/        OperatingSystem getOSType = 'linux' ifTrue:[
   519 "/        OperatingSystem getOSType = 'linux' ifTrue:[
   488 "/            cmd := 'cp -rv ../../* ' , fullDir.
   520 "/            cmd := 'cp -rv ../../* ' , fullDir.
   535 
   567 
   536         fileName := entry key.
   568         fileName := entry key.
   537         destDir := entry value.
   569         destDir := entry value.
   538 
   570 
   539         ((fileName includes:$*)
   571         ((fileName includes:$*)
   540         or:[('../../' , fileName) asFilename exists])ifTrue:[
   572         or:[(topDirPrefix , fileName) asFilename exists])ifTrue:[
   541             actionPercentageHolder value:(nDone / numFiles * 100) rounded.
   573             actionPercentageHolder value:(nDone / numFiles * 100) rounded.
   542 
   574 
   543             msg at:4 put:'    ' , (fileName asText allBold).
   575             msg at:4 put:'    ' , (fileName asText allBold).
   544             msg at:6 put:'    ' , (destDir asText allBold).
   576             msg at:6 put:'    ' , (destDir asText allBold).
   545             actionTextHolder value:nil.
   577             actionTextHolder value:nil.
   550                 (self listOfOptionalPackages includes:fileName) ifFalse:[
   582                 (self listOfOptionalPackages includes:fileName) ifFalse:[
   551                     commandTraceView showCR:('cannot copy ' , fileName , ' - not included in distribution').
   583                     commandTraceView showCR:('cannot copy ' , fileName , ' - not included in distribution').
   552                     commandTraceView endEntry.
   584                     commandTraceView endEntry.
   553                 ]
   585                 ]
   554             ] ifFalse:[
   586             ] ifFalse:[
   555                 cmd := 'cp -r ../../' , fileName , ' ' , destDir.
   587                 self recursiveCopy:(topDirPrefix , fileName) to:destDir.
   556                 commandTraceView showCR:cmd , ' ...'.
       
   557                 commandTraceView endEntry.
       
   558                 cmd := cmd , ' 2>&1' .
       
   559 
       
   560                 self executeCommandAndShowOutput:cmd
       
   561             ]
   588             ]
   562         ].
   589         ].
   563 
   590 
   564         nDone := nDone + 1
   591         nDone := nDone + 1
   565     ].
   592     ].
   569     "
   596     "
   570      STXInstaller open
   597      STXInstaller open
   571     "
   598     "
   572 
   599 
   573     "Created: / 17.7.1996 / 15:16:20 / cg"
   600     "Created: / 17.7.1996 / 15:16:20 / cg"
   574     "Modified: / 20.4.1998 / 17:41:45 / cg"
   601     "Modified: / 31.5.1999 / 13:05:23 / cg"
   575 !
   602 !
   576 
   603 
   577 createDirectories
   604 createDirectories
   578     |msg dirsToMake numDirs nDone|
   605     |msg dirsToMake numDirs nDone|
   579 
   606 
   637 !
   664 !
   638 
   665 
   639 createSymbolicLinks
   666 createSymbolicLinks
   640     |msg dirsToMake numDirs nDone|
   667     |msg dirsToMake numDirs nDone|
   641 
   668 
       
   669     OperatingSystem isUNIXlike ifFalse:[^ self].
       
   670 
   642     msg := (resources array:#('ST/X Installation' '' 'creating symbolic links' '' '' '')) asStringCollection.
   671     msg := (resources array:#('ST/X Installation' '' 'creating symbolic links' '' '' '')) asStringCollection.
   643 
   672 
   644     commandTraceView showCR:(resources string:'setting up symbolic links in doc/online ...').
   673     commandTraceView showCR:(resources string:'setting up symbolic links in doc/online ...').
   645     commandTraceView endEntry.
   674     commandTraceView endEntry.
   646     installWhat == #full ifTrue:[
   675     installWhat == #full ifTrue:[
   648     ] ifFalse:[
   677     ] ifFalse:[
   649         OperatingSystem executeCommand:('(cd ' , stxLibDir , '/doc/online ; make links)').
   678         OperatingSystem executeCommand:('(cd ' , stxLibDir , '/doc/online ; make links)').
   650     ].
   679     ].
   651 
   680 
   652     "Created: / 17.7.1996 / 15:24:19 / cg"
   681     "Created: / 17.7.1996 / 15:24:19 / cg"
   653     "Modified: / 20.4.1998 / 15:40:11 / cg"
   682     "Modified: / 31.5.1999 / 13:26:42 / cg"
   654 !
   683 !
   655 
   684 
   656 executeCommandAndShowOutput:cmd
   685 executeCommandAndShowOutput:cmd
   657     |doneSemaphore line p|
   686     |doneSemaphore line p|
   658 
   687 
   734 
   763 
   735     Delay waitForSeconds:2.
   764     Delay waitForSeconds:2.
   736 
   765 
   737     "Created: 2.3.1997 / 12:49:52 / cg"
   766     "Created: 2.3.1997 / 12:49:52 / cg"
   738     "Modified: 8.8.1997 / 17:47:06 / cg"
   767     "Modified: 8.8.1997 / 17:47:06 / cg"
       
   768 !
       
   769 
       
   770 recursiveCopy:src to:destDir
       
   771     |cmd|
       
   772 
       
   773     OperatingSystem isUNIXlike ifTrue:[
       
   774         cmd := 'cp -r ' , src , ' ' , destDir.
       
   775         commandTraceView showCR:cmd , ' ...'.
       
   776         commandTraceView endEntry.
       
   777         cmd := cmd , ' 2>&1' .
       
   778 
       
   779         self executeCommandAndShowOutput:cmd
       
   780     ] ifFalse:[
       
   781         commandTraceView showCR:('copy ' , src , ' ' , destDir).
       
   782         commandTraceView endEntry.
       
   783         src includesMatchCharacters ifTrue:[
       
   784             src asFilename directory directoryContents do:[:fileName |
       
   785                 ((src asFilename baseName) match:fileName) ifTrue:[
       
   786                     (src asFilename directory construct:fileName)
       
   787                         recursiveCopyTo:destDir
       
   788                 ]
       
   789             ]
       
   790         ] ifFalse:[
       
   791             src asFilename recursiveCopyTo:destDir
       
   792         ]
       
   793     ]
       
   794 
       
   795     "Created: / 31.5.1999 / 13:05:09 / cg"
       
   796     "Modified: / 31.5.1999 / 13:14:19 / cg"
   739 ! !
   797 ! !
   740 
   798 
   741 !STXInstaller methodsFor:'startup'!
   799 !STXInstaller methodsFor:'startup'!
   742 
   800 
   743 askAndInstall
   801 askAndInstall
   745 
   803 
   746     |answer here|
   804     |answer here|
   747 
   805 
   748     resources := ResourcePack for:self class.
   806     resources := ResourcePack for:self class.
   749 
   807 
   750     ((here := Filename currentDirectory pathName) endsWith:'projects/smalltalk') ifFalse:[
   808     (((here := Filename currentDirectory pathName) endsWith:'projects/smalltalk') not
   751         (here endsWith:'stx\binbc') ifFalse:[
   809     and:[(here asLowercase endsWith:'stx\binbc') not
   752             self warn:(resources string:'must be in the ''projects/smalltalk'' directory').
   810     and:[(here asLowercase endsWith:'projects\smalltalk') not
   753             ^ self
   811     ]]) ifTrue:[
   754         ]
   812         self warn:(resources string:'must be in the ''projects/smalltalk'' directory').
       
   813         ^ self
   755     ].
   814     ].
   756 
   815 
   757     answer := self askForFullInstallation.
   816     answer := self askForFullInstallation.
   758     answer ifFalse:[^ self].
   817     answer ifFalse:[^ self].
   759 
   818 
   769                 ^ self
   828                 ^ self
   770             ]
   829             ]
   771         ]
   830         ]
   772     ].
   831     ].
   773 
   832 
   774     "Modified: / 30.4.1999 / 11:53:35 / cg"
   833     "Modified: / 31.5.1999 / 12:04:14 / cg"
   775 !
   834 !
   776 
   835 
   777 askForDestination
   836 askForDestination
   778     "open a dialog to enter destination directories"
   837     "open a dialog to enter destination directories"
   779 
   838 
   871 
   930 
   872 askForDestinationForPartialInstallation
   931 askForDestinationForPartialInstallation
   873     "open a dialog to enter destination directories"
   932     "open a dialog to enter destination directories"
   874 
   933 
   875     |d cm l green dark img
   934     |d cm l green dark img
   876      stxLibDirHolder stxLibBinDirHolder stxBinDirHolder
   935      stxInstDirHolder stxLibDirHolder stxLibBinDirHolder stxBinDirHolder
   877      installDocHolder installSourceHolder installSTCHolder installGoodiesHolder
   936      installDocHolder installSourceHolder installSTCHolder installGoodiesHolder
   878      binMegabytes libMegabytes docMegabytes stcMegabytes srcMegabytes
   937      binMegabytes libMegabytes docMegabytes stcMegabytes srcMegabytes
   879      goodyMegabytes
   938      goodyMegabytes stxRel list stxInstDir
   880     |
   939     |
   881 
   940 
   882     binMegabytes := 12.
   941     binMegabytes := 12.
   883     libMegabytes := 30.
   942     libMegabytes := 30.
   884     docMegabytes := 15.
   943     docMegabytes := 15.
   885     stcMegabytes := 2.
   944     stcMegabytes := 2.
   886     srcMegabytes := 25.
   945     srcMegabytes := 25.
   887     goodyMegabytes := 2.
   946     goodyMegabytes := 2.
   888 
   947 
       
   948     stxRel := self smalltalkRelease.
       
   949 
   889     OperatingSystem isMSWINDOWSlike ifTrue:[
   950     OperatingSystem isMSWINDOWSlike ifTrue:[
   890         LastLibDir isNil ifTrue:[
   951         LastPartialDir isNil ifTrue:[
   891             LastLibDir := '\Programme\SmalltalkX\' , self smalltalkRelease , '\lib'
   952             LastPartialDir := 'c:\Programme\SmalltalkX\' , stxRel 
   892         ].
   953         ].
   893         LastLibBinDir isNil ifTrue:[
   954 "/        LastLibDir isNil ifTrue:[
   894             LastLibBinDir := '\Programme\SmalltalkX\' , self smalltalkRelease , '\lib'
   955 "/            LastLibDir := 'c:\Programme\SmalltalkX\' , stxRel , '\lib'
       
   956 "/        ].
       
   957 "/        LastLibBinDir isNil ifTrue:[
       
   958 "/            LastLibBinDir := 'c:\Programme\SmalltalkX\' , stxRel , '\lib'
       
   959 "/        ].
       
   960 "/        LastBinDir isNil ifTrue:[
       
   961 "/            LastBinDir := 'c:\Programme\SmalltalkX\' , stxRel , '\bin'
       
   962 "/        ].
       
   963     ] ifFalse:[
       
   964         LastPartialDir isNil ifTrue:[
       
   965             LastPartialDir := '/opt/smalltalk/' , stxRel
   895         ].
   966         ].
   896         LastBinDir isNil ifTrue:[
   967 "/        LastLibDir isNil ifTrue:[
   897             LastBinDir := '\Programme\SmalltalkX\' , self smalltalkRelease , '\lib'
   968 "/            LastLibDir := '/opt/smalltalk/' , stxRel , '/lib'
   898         ].
   969 "/        ].
   899     ] ifFalse:[
   970 "/        LastLibBinDir isNil ifTrue:[
   900         LastLibDir isNil ifTrue:[
   971 "/            LastLibBinDir := '/opt/smalltalk/' , stxRel , '/lib'
   901             LastLibDir := '/opt/smalltalk/' , self smalltalkRelease , '/lib'
   972 "/        ].
   902         ].
   973 "/        LastBinDir isNil ifTrue:[
   903         LastLibBinDir isNil ifTrue:[
   974 "/            LastBinDir := '/opt/smalltalk/' , stxRel , '/bin'
   904             LastLibBinDir := '/opt/smalltalk/' , self smalltalkRelease , '/lib'
   975 "/        ].
   905         ].
   976     ].
   906         LastBinDir isNil ifTrue:[
   977 
   907             LastBinDir := '/opt/smalltalk/' , self smalltalkRelease , '/bin'
   978     stxInstDirHolder := LastPartialDir asValue.
   908         ].
   979 "/    stxLibDirHolder := LastLibDir asValue.
   909     ].
   980 "/    stxLibBinDirHolder := LastLibBinDir asValue.
   910 
   981 "/    stxBinDirHolder := LastBinDir asValue.
   911     stxLibDirHolder := LastLibDir asValue.
       
   912     stxLibBinDirHolder := LastLibBinDir asValue.
       
   913     stxBinDirHolder := LastBinDir asValue.
       
   914 
   982 
   915     installDocHolder := true asValue.
   983     installDocHolder := true asValue.
   916     installSourceHolder := true asValue.
   984     installSourceHolder := true asValue.
   917     installSTCHolder := true asValue.
   985     installSTCHolder := true asValue.
   918     installGoodiesHolder := true asValue.
   986     installGoodiesHolder := true asValue.
   941     d addHorizontalLine.
  1009     d addHorizontalLine.
   942 
  1010 
   943     l := d addTextLabel:(resources string:'Destination directories:').
  1011     l := d addTextLabel:(resources string:'Destination directories:').
   944     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
  1012     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
   945 
  1013 
   946     l := d addTextLabel:(resources string:'(the defaults below are recommended)').
  1014     l := d addTextLabel:(resources string:'(the default below is recommended)').
   947     l adjust:#right; backgroundColor:dark; foregroundColor:Color white.
  1015     l adjust:#right; backgroundColor:dark; foregroundColor:Color white.
   948 
  1016 
   949     cm := ComboBoxView on:stxBinDirHolder.
  1017     cm := ComboBoxView on:stxInstDirHolder.
   950     cm list:self defaultBinDirs.
  1018     list := self defaultBinDirs collect:[:line |
       
  1019                 line replChar:$\ withString:'\\'
       
  1020             ].
       
  1021     cm list:list.
   951     d 
  1022     d 
   952         addLabelledField:cm 
  1023         addLabelledField:cm 
   953         label:(resources string:'binaries')
  1024         label:(resources string:'install into:')
   954         adjust:#left 
  1025         adjust:#left 
   955         tabable:true 
  1026         tabable:true 
   956         from:0.0 to:1.0 separateAtX:0.25
  1027         from:0.0 to:1.0 separateAtX:0.25
   957         nameAs:'binaryBox'.
  1028         nameAs:'instDirBox'.
   958 
  1029 
   959     (d componentAt:'binaryBox.label') backgroundColor:dark; foregroundColor:Color white.
  1030     (d componentAt:'instDirBox.label') backgroundColor:dark; foregroundColor:Color white.
   960 
  1031 
   961     cm := ComboBoxView on:stxLibBinDirHolder.
  1032 "/    cm := ComboBoxView on:stxBinDirHolder.
   962     cm list:self defaultLibBinDirs.
  1033 "/    list := self defaultBinDirs collect:[:line |
   963     d 
  1034 "/                line replChar:$\ withString:'\\'
   964         addLabelledField:cm 
  1035 "/            ].
   965         label:(resources string:'libraries') 
  1036 "/    cm list:list.
   966         adjust:#left 
  1037 "/    d 
   967         tabable:true 
  1038 "/        addLabelledField:cm 
   968         from:0.0 to:1.0 separateAtX:0.25
  1039 "/        label:(resources string:'binaries')
   969         nameAs:'libraryBinBox'.
  1040 "/        adjust:#left 
   970 
  1041 "/        tabable:true 
   971     (d componentAt:'libraryBinBox.label') backgroundColor:dark; foregroundColor:Color white.
  1042 "/        from:0.0 to:1.0 separateAtX:0.25
   972 
  1043 "/        nameAs:'binaryBox'.
   973     cm := ComboBoxView on:stxLibDirHolder.
  1044 "/
   974     cm list:self defaultLibDirs.
  1045 "/    (d componentAt:'binaryBox.label') backgroundColor:dark; foregroundColor:Color white.
   975     d 
  1046 "/
   976         addLabelledField:cm 
  1047 "/    cm := ComboBoxView on:stxLibBinDirHolder.
   977         label:(resources string:'other files') 
  1048 "/    cm list:self defaultLibBinDirs.
   978         adjust:#left 
  1049 "/    d 
   979         tabable:true 
  1050 "/        addLabelledField:cm 
   980         from:0.0 to:1.0 separateAtX:0.25
  1051 "/        label:(resources string:'libraries') 
   981         nameAs:'libraryBox'.
  1052 "/        adjust:#left 
   982 
  1053 "/        tabable:true 
   983     (d componentAt:'libraryBox.label') backgroundColor:dark; foregroundColor:Color white.
  1054 "/        from:0.0 to:1.0 separateAtX:0.25
       
  1055 "/        nameAs:'libraryBinBox'.
       
  1056 "/
       
  1057 "/    (d componentAt:'libraryBinBox.label') backgroundColor:dark; foregroundColor:Color white.
       
  1058 "/
       
  1059 "/    cm := ComboBoxView on:stxLibDirHolder.
       
  1060 "/    cm list:self defaultLibDirs.
       
  1061 "/    d 
       
  1062 "/        addLabelledField:cm 
       
  1063 "/        label:(resources string:'other files') 
       
  1064 "/        adjust:#left 
       
  1065 "/        tabable:true 
       
  1066 "/        from:0.0 to:1.0 separateAtX:0.25
       
  1067 "/        nameAs:'libraryBox'.
       
  1068 "/
       
  1069 "/    (d componentAt:'libraryBox.label') backgroundColor:dark; foregroundColor:Color white.
   984 
  1070 
   985     d addVerticalSpace.
  1071     d addVerticalSpace.
   986     d addHorizontalLine.
  1072     d addHorizontalLine.
   987     d addVerticalSpace.
  1073     d addVerticalSpace.
   988 
  1074 
  1030 
  1116 
  1031     d allViewBackground:dark.
  1117     d allViewBackground:dark.
  1032 
  1118 
  1033     d openAtCenter.
  1119     d openAtCenter.
  1034     d accepted ifTrue:[
  1120     d accepted ifTrue:[
  1035         stxLibDir := LastLibDir := stxLibDirHolder value.
  1121         stxInstDir := LastPartialDir := stxInstDirHolder value.
  1036         stxLibBinDir := LastLibBinDir := stxLibBinDirHolder value.
  1122         stxLibDir := stxInstDir asFilename constructString:'lib'.
  1037         stxBinDir := LastBinDir := stxBinDirHolder value.
  1123         stxLibBinDir := stxInstDir asFilename constructString:'lib'.
       
  1124         stxBinDir := stxInstDir asFilename constructString:'bin'.
       
  1125 
       
  1126 "/        stxLibDir := LastLibDir := stxLibDirHolder value.
       
  1127 "/        stxLibBinDir := LastLibBinDir := stxLibBinDirHolder value.
       
  1128 "/        stxBinDir := LastBinDir := stxBinDirHolder value.
  1038         installDocFiles := installDocHolder value.
  1129         installDocFiles := installDocHolder value.
  1039         installSourceFiles := installSourceHolder value.
  1130         installSourceFiles := installSourceHolder value.
  1040         installSTCFiles := installSTCHolder value.
  1131         installSTCFiles := installSTCHolder value.
  1041         installGoodyFiles := installGoodiesHolder value.
  1132         installGoodyFiles := installGoodiesHolder value.
  1042         d destroy.
  1133         d destroy.
  1048     "
  1139     "
  1049      STXInstaller open
  1140      STXInstaller open
  1050     "
  1141     "
  1051 
  1142 
  1052     "Created: / 25.2.1998 / 17:11:26 / cg"
  1143     "Created: / 25.2.1998 / 17:11:26 / cg"
  1053     "Modified: / 30.4.1999 / 11:58:33 / cg"
  1144     "Modified: / 31.5.1999 / 13:42:48 / cg"
  1054 !
  1145 !
  1055 
  1146 
  1056 askForFullInstallation
  1147 askForFullInstallation
  1057     "open a dialog to enter destination directories"
  1148     "open a dialog to enter destination directories"
  1058 
  1149 
  1199 
  1290 
  1200                 (OperatingSystem recursiveRemoveDirectory:whichDir)
  1291                 (OperatingSystem recursiveRemoveDirectory:whichDir)
  1201                 ifFalse:[
  1292                 ifFalse:[
  1202                     self warn:(resources string:'mhmh - could not remove old installation.
  1293                     self warn:(resources string:'mhmh - could not remove old installation.
  1203 
  1294 
  1204 Please remove it manually (using root privileges if required) 
  1295 Please remove it manually (using administrator privileges if required) 
  1205 and try again.').
  1296 and try again.').
  1206                     box destroy.
  1297                     box destroy.
  1207                     ^ false
  1298                     ^ false
  1208                 ].
  1299                 ].
  1209 
  1300 
  1215 
  1306 
  1216     "
  1307     "
  1217      STXInstaller open
  1308      STXInstaller open
  1218     "
  1309     "
  1219 
  1310 
  1220     "Modified: / 25.2.1998 / 19:35:12 / cg"
  1311     "Modified: / 31.5.1999 / 13:23:03 / cg"
  1221 !
  1312 !
  1222 
  1313 
  1223 doInstall
  1314 doInstall
  1224     "install ST/X; return true if ok, false if not"
  1315     "install ST/X; return true if ok, false if not"
  1225 
  1316 
  1226     |progressView ok v textView p l 
  1317     |progressView ok v textView p l 
  1227      dirToMonitor doDfMonitoring dfMonitorProcess kB|
  1318      dirToMonitor doDfMonitoring dfMonitorProcess kB drive|
  1228 
  1319 
  1229     doDfMonitoring := false.
  1320     doDfMonitoring := false.
  1230 
  1321 
  1231     v := View new preferredExtent:(250 @ 350).
  1322     v := View new preferredExtent:(250 @ 350).
  1232 
  1323 
  1239         dirToMonitor := fullDir.
  1330         dirToMonitor := fullDir.
  1240     ] ifFalse:[
  1331     ] ifFalse:[
  1241         dirToMonitor := stxLibDir
  1332         dirToMonitor := stxLibDir
  1242     ].
  1333     ].
  1243 
  1334 
  1244     (OperatingSystem isMSWINDOWSlike not
  1335     OperatingSystem isMSWINDOWSlike ifTrue:[
  1245     and:[OperatingSystem canExecuteCommand:'df ' , dirToMonitor]) ifTrue:[
  1336         drive := Filename rootDirectoryOnVolume:(dirToMonitor asFilename volume)
  1246         p := HorizontalPanelView in:v.
  1337     ] ifFalse:[
  1247         p origin:0.0@1.0 corner:1.0@1.0.
  1338         drive := dirToMonitor
  1248         p topInset:-30.
  1339     ].
  1249         p horizontalLayout:#fit.
  1340 
  1250 
  1341     p := HorizontalPanelView in:v.
  1251         l := Label label:'' in:p.
  1342     p origin:0.0@1.0 corner:1.0@1.0.
  1252         l labelChannel:(dfHolder := '' asValue).
  1343     p topInset:-30.
  1253         l adjust:#left.
  1344     p horizontalLayout:#fit.
  1254         dfMonitorProcess := [
  1345 
  1255             |ok p text keys values i l|
  1346     l := Label label:'' in:p.
  1256 
  1347     l labelChannel:(dfHolder := '' asValue).
  1257             ok := true.
  1348     l adjust:#left.
  1258             [ok] whileTrue:[
  1349     dfMonitorProcess := [
  1259                 doDfMonitoring ifTrue:[
  1350         |ok info free kB i l|
  1260                     ok := false.
  1351 
  1261                     p := PipeStream readingFrom:('df -k ' , dirToMonitor).
  1352         ok := true.
  1262                     p notNil ifTrue:[
  1353         [ok] whileTrue:[
  1263                        [
  1354             doDfMonitoring ifTrue:[
  1264                            text := p contentsOfEntireFile.
  1355                 ok := false.
  1265                        ] valueNowOrOnUnwindDo:[
  1356                 info := OperatingSystem getDiskInfoOf:drive pathName.
  1266                            p close.
  1357                 info notNil ifTrue:[
  1267                        ].
  1358                     free := info at:#freeBytes ifAbsent:nil.
  1268 "/ Transcript showCR:text asString.
  1359                     free notNil ifTrue:[
  1269                        text notNil ifTrue:[
  1360                         kB := free / 1024.
  1270                            text := text asCollectionOfLines.
  1361                         kB > 10000 ifTrue:[
  1271                            text size >= 2 ifTrue:[
  1362                             l := (kB // 1024) printString, 'Mb available.'.
  1272                                keys := (text at:1) asCollectionOfWords.
  1363                         ] ifFalse:[
  1273                                values := (text at:2) asCollectionOfWords.
  1364                             l := kB printString , 'Kb available.'.
  1274                                i := (keys indexOf:'Capacity').
       
  1275                                i == 0 ifTrue:[
       
  1276                                    i := (keys indexOf:'capacity').
       
  1277                                ].
       
  1278                                i ~~ 0 ifTrue:[
       
  1279                                    l := 'Used disk space: ' , (values at:i) withoutSeparators.
       
  1280                                    i := (keys indexOf:'Available').
       
  1281                                    i == 0 ifTrue:[
       
  1282                                        i := (keys indexOf:'available').
       
  1283                                        i == 0 ifTrue:[
       
  1284                                            i := (keys indexOf:'avail').
       
  1285                                            i == 0 ifTrue:[
       
  1286                                                i := (keys indexOf:'Avail').
       
  1287                                            ].
       
  1288                                        ].
       
  1289                                    ].
       
  1290                                    i ~~ 0 ifTrue:[
       
  1291                                         kB := (values at:i) withoutSeparators.
       
  1292                                         l := l , ' (' , kB , 'k available)'.
       
  1293                                    ].
       
  1294                                    dfHolder value:l.
       
  1295                                    ok := true.
       
  1296                                    Delay waitForSeconds:9.
       
  1297                                ]
       
  1298                            ]
       
  1299                         ].
  1365                         ].
       
  1366                         dfHolder value:l.
       
  1367                         ok := true.
       
  1368                         Delay waitForSeconds:9.
  1300                     ].
  1369                     ].
  1301                 ].
  1370                 ].
  1302                 Delay waitForSeconds:1.
  1371             ].
  1303             ]
  1372             Delay waitForSeconds:1.
  1304         ] forkAt:(Processor activePriority+3)
  1373         ]
  1305     ].
  1374     ] forkAt:(Processor activePriority+3).
  1306 
  1375 
  1307     progressView := ProgressIndicator
  1376     progressView := ProgressIndicator
  1308                         inBoxWithLabel:'ST/X Installation' icon:(Icon stxIcon)
  1377                         inBoxWithLabel:'ST/X Installation' icon:(Icon stxIcon)
  1309                         text:#('ST/X Installation' '' '' '' '' '' '' '') asStringCollection
  1378                         text:#('ST/X Installation' '' '' '' '' '' '' '') asStringCollection
  1310                         abortable:true
  1379                         abortable:true
  1373     "
  1442     "
  1374      STXInstaller open
  1443      STXInstaller open
  1375     "
  1444     "
  1376 
  1445 
  1377     "Created: / 17.7.1996 / 15:11:27 / cg"
  1446     "Created: / 17.7.1996 / 15:11:27 / cg"
  1378     "Modified: / 30.4.1999 / 17:53:53 / cg"
  1447     "Modified: / 31.5.1999 / 14:05:38 / cg"
  1379 !
  1448 !
  1380 
  1449 
  1381 open
  1450 open
  1382     self askAndInstall.
  1451     self askAndInstall.
  1383 
  1452 
  1384     "
  1453     "
  1385      LastLibDir := LastBinDir := LastLibBinDir := nil.
  1454      LastLibDir := LastBinDir := LastLibBinDir := nil.
       
  1455      LastPartialDir := nil.
  1386 
  1456 
  1387      STXInstaller open
  1457      STXInstaller open
  1388     "
  1458     "
  1389 
  1459 
  1390     "Modified: / 30.4.1999 / 11:59:00 / cg"
  1460     "Modified: / 31.5.1999 / 13:41:27 / cg"
  1391 !
  1461 !
  1392 
  1462 
  1393 postInstall
  1463 postInstall
  1394     "some messages at the end ..."
  1464     "some messages at the end ..."
  1395 
  1465