STXInstaller.st
changeset 678 4dd439ebf162
parent 277 935f9a055594
child 682 9fcd010d8fd3
equal deleted inserted replaced
677:aa0b1c1ebfe6 678:4dd439ebf162
     1 Object subclass:#STXInstaller
     1 Object subclass:#STXInstaller
     2 	instanceVariableNames:'stxLibDir stxLibBinDir stxBinDir installDocFiles
     2 	instanceVariableNames:'stxLibDir stxLibBinDir stxBinDir installDocFiles
     3 		installSourceFiles installSTCFiles installGoodyFiles
     3 		installSourceFiles installSTCFiles installGoodyFiles fullDir
     4 		actionPercentageHolder actionTextHolder commandTraceView
     4 		actionPercentageHolder actionTextHolder commandTraceView
     5 		resources'
     5 		resources fullInstallation dfHolder copyProcess'
     6 	classVariableNames:'LastBinDir LastLibBinDir LastLibDir'
     6 	classVariableNames:'LastBinDir LastLibBinDir LastLibDir LastFullDir'
     7 	poolDictionaries:''
     7 	poolDictionaries:''
     8 	category:'eXept-tools'
     8 	category:'eXept-tools'
     9 !
     9 !
    10 
    10 
    11 
    11 
    46 "/                            f exists and:[f isDirectory]].
    46 "/                            f exists and:[f isDirectory]].
    47     ^ dirs sort
    47     ^ dirs sort
    48 
    48 
    49     "Created: 18.7.1996 / 19:43:00 / cg"
    49     "Created: 18.7.1996 / 19:43:00 / cg"
    50     "Modified: 18.7.1996 / 19:45:08 / cg"
    50     "Modified: 18.7.1996 / 19:45:08 / cg"
       
    51 !
       
    52 
       
    53 defaultFullDirs
       
    54     |dirs|
       
    55 
       
    56     dirs := OrderedCollection new.
       
    57     dirs add:(Filename homeDirectory constructString:'stxDevelop').
       
    58     dirs add:((Filename homeDirectory 
       
    59                             construct:'stx')
       
    60                             constructString:'develop').
       
    61     ('/home' asFilename exists and:['/home' asFilename isDirectory]) ifTrue:[
       
    62         dirs add:'/home/stx/develop'.
       
    63     ].
       
    64 
       
    65     ^ dirs sort
       
    66 
       
    67     "Modified: / 18.7.1996 / 19:45:08 / cg"
       
    68     "Created: / 25.2.1998 / 17:14:43 / cg"
    51 !
    69 !
    52 
    70 
    53 defaultLibBinDirs
    71 defaultLibBinDirs
    54     |dirs|
    72     |dirs|
    55 
    73 
   102 
   120 
   103 directoriesToMake
   121 directoriesToMake
   104     |dirsToMake|
   122     |dirsToMake|
   105 
   123 
   106     dirsToMake := OrderedCollection new.
   124     dirsToMake := OrderedCollection new.
   107     dirsToMake add:stxBinDir.
   125     fullInstallation ifTrue:[
   108     dirsToMake add:stxLibDir.
   126         dirsToMake add:fullDir.
   109     dirsToMake add:stxLibBinDir.
   127     ] ifFalse:[
   110     dirsToMake add:(stxLibDir asFilename constructString:'configurations').
   128         dirsToMake add:stxBinDir.
   111     dirsToMake add:(stxLibDir asFilename constructString:'doc').
   129         dirsToMake add:stxLibDir.
   112     dirsToMake add:(stxLibDir asFilename constructString:'doc/online').
   130         dirsToMake add:stxLibBinDir.
   113     dirsToMake add:(stxLibDir asFilename constructString:'doc/online/english').
   131         dirsToMake add:(stxLibDir asFilename constructString:'configurations').
   114     dirsToMake add:(stxLibDir asFilename constructString:'doc/online/german').
   132         dirsToMake add:(stxLibDir asFilename constructString:'doc').
   115     dirsToMake add:(stxLibDir asFilename constructString:'doc/online/french').
   133         dirsToMake add:(stxLibDir asFilename constructString:'doc/online').
   116     dirsToMake add:(stxLibDir asFilename constructString:'doc/online/italian').
   134         dirsToMake add:(stxLibDir asFilename constructString:'doc/online/english').
   117     dirsToMake add:(stxLibDir asFilename constructString:'include').
   135         dirsToMake add:(stxLibDir asFilename constructString:'doc/online/german').
   118     dirsToMake add:(stxLibDir asFilename constructString:'resources').
   136         dirsToMake add:(stxLibDir asFilename constructString:'doc/online/french').
   119     dirsToMake add:(stxLibDir asFilename constructString:'binary').
   137         dirsToMake add:(stxLibDir asFilename constructString:'doc/online/italian').
   120     dirsToMake add:(stxLibDir asFilename constructString:'bitmaps').
   138         dirsToMake add:(stxLibDir asFilename constructString:'include').
   121     dirsToMake add:(stxLibDir asFilename constructString:'goodies').
   139         dirsToMake add:(stxLibDir asFilename constructString:'resources').
   122 
   140         dirsToMake add:(stxLibDir asFilename constructString:'binary').
       
   141         dirsToMake add:(stxLibDir asFilename constructString:'bitmaps').
       
   142         dirsToMake add:(stxLibDir asFilename constructString:'goodies').
       
   143     ].
   123     ^ dirsToMake
   144     ^ dirsToMake
       
   145 
       
   146     "Modified: / 25.2.1998 / 17:15:19 / cg"
   124 !
   147 !
   125 
   148 
   126 listOfOptionalPackages
   149 listOfOptionalPackages
   127     ^ #(
   150     ^ #(
   128         'libDB'
   151         'libDB'
   238 ! !
   261 ! !
   239 
   262 
   240 !STXInstaller methodsFor:'installing'!
   263 !STXInstaller methodsFor:'installing'!
   241 
   264 
   242 copyFiles
   265 copyFiles
   243     |msg fileSpec filesToCopy numFiles nDone|
   266     |msg fileSpec filesToCopy numFiles nDone cmd|
   244 
   267 
   245     msg := (resources array:#('ST/X Installation' '' 'copying:' '' 'to:' '')) asStringCollection.
   268      msg := (resources array:#('ST/X Installation' '' 'copying:' '' 'to:' '')) asStringCollection.
       
   269 
       
   270     fullInstallation ifTrue:[
       
   271         msg at:4 put:('    all from CD' asText allBold).
       
   272         msg at:6 put:'    ' , (fullDir asText allBold).
       
   273         actionTextHolder value:nil.
       
   274         actionTextHolder value:msg.
       
   275 
       
   276         cmd := 'cp -r ../../* ' , fullDir.
       
   277         "/
       
   278         "/ not all systems have cp -rv
       
   279         "/
       
   280         OperatingSystem getOSType = 'linux' ifTrue:[
       
   281             cmd := 'cp -rv ../../* ' , fullDir.
       
   282         ].
       
   283         commandTraceView showCR:cmd , ' ...'.
       
   284         commandTraceView endEntry.
       
   285         cmd := cmd , ' 2>&1' .
       
   286 
       
   287         self executeCommandAndShowOutput:cmd.
       
   288 
       
   289         ^ true
       
   290     ].
   246 
   291 
   247     fileSpec := self specOfFilesToCopy.
   292     fileSpec := self specOfFilesToCopy.
   248 
   293 
   249     filesToCopy := OrderedCollection new.
   294     filesToCopy := OrderedCollection new.
   250 
   295 
   276 
   321 
   277     numFiles := filesToCopy size.
   322     numFiles := filesToCopy size.
   278     nDone := 0.
   323     nDone := 0.
   279 
   324 
   280     filesToCopy do:[:entry |
   325     filesToCopy do:[:entry |
   281         |fileName destDir cmd p text line doneSemaphore|
   326         |fileName destDir cmd|
   282 
   327 
   283         fileName := entry key.
   328         fileName := entry key.
   284         destDir := entry value.
   329         destDir := entry value.
   285 
   330 
   286         ((fileName includes:$*)
   331         ((fileName includes:$*)
   302                 cmd := 'cp -r ../../' , fileName , ' ' , destDir.
   347                 cmd := 'cp -r ../../' , fileName , ' ' , destDir.
   303                 commandTraceView showCR:cmd , ' ...'.
   348                 commandTraceView showCR:cmd , ' ...'.
   304                 commandTraceView endEntry.
   349                 commandTraceView endEntry.
   305                 cmd := cmd , ' 2>&1' .
   350                 cmd := cmd , ' 2>&1' .
   306 
   351 
   307                 doneSemaphore := Semaphore new.
   352                 self executeCommandAndShowOutput:cmd
   308 
       
   309                 [   
       
   310 
       
   311                     p := PipeStream readingFrom:cmd.
       
   312                     p isNil ifTrue:[
       
   313                         self warn:('command error. Could not execute:\\' , cmd) withCRs.
       
   314                     ] ifFalse:[
       
   315                         [p atEnd] whileFalse:[
       
   316                             (p readWaitWithTimeout:0.1) ifFalse:[
       
   317                                 line := p nextLine.
       
   318                                 (line notNil and:[line notEmpty]) ifTrue:[
       
   319                                     commandTraceView showCR:(('  ' , line) asText emphasizeAllWith:(#color->Color red)).
       
   320                                     commandTraceView endEntry.
       
   321                                 ]
       
   322                             ]
       
   323                         ].
       
   324                         p close.
       
   325                     ].
       
   326                     doneSemaphore signal.
       
   327                 ] forkAt:4.
       
   328 
       
   329                 doneSemaphore wait.
       
   330             ]
   353             ]
   331         ].
   354         ].
   332 
   355 
   333         nDone := nDone + 1
   356         nDone := nDone + 1
   334     ].
   357     ].
   335 
   358 
   336     ^ true
   359     ^ true
   337 
   360 
   338     "Created: 17.7.1996 / 15:16:20 / cg"
   361     "
   339     "Modified: 22.5.1997 / 15:06:33 / cg"
   362      STXInstaller open
       
   363     "
       
   364 
       
   365     "Created: / 17.7.1996 / 15:16:20 / cg"
       
   366     "Modified: / 25.2.1998 / 18:30:53 / cg"
   340 !
   367 !
   341 
   368 
   342 createDirectories
   369 createDirectories
   343     |msg dirsToMake numDirs nDone|
   370     |msg dirsToMake numDirs nDone|
   344 
   371 
   406 
   433 
   407     msg := (resources array:#('ST/X Installation' '' 'creating symbolic links' '' '' '')) asStringCollection.
   434     msg := (resources array:#('ST/X Installation' '' 'creating symbolic links' '' '' '')) asStringCollection.
   408 
   435 
   409     commandTraceView showCR:(resources string:'setting up symbolic links in doc/online ...').
   436     commandTraceView showCR:(resources string:'setting up symbolic links in doc/online ...').
   410     commandTraceView endEntry.
   437     commandTraceView endEntry.
   411     OperatingSystem executeCommand:('(cd ' , stxLibDir , '/doc/online ; make links)').
   438     fullInstallation ifTrue:[
       
   439         OperatingSystem executeCommand:('(cd ' , fullDir , '/doc/online ; make links)').
       
   440     ] ifFalse:[
       
   441         OperatingSystem executeCommand:('(cd ' , stxLibDir , '/doc/online ; make links)').
       
   442     ].
   412     ^ true
   443     ^ true
   413 
   444 
   414     "Created: 17.7.1996 / 15:24:19 / cg"
   445     "Created: / 17.7.1996 / 15:24:19 / cg"
   415     "Modified: 22.5.1997 / 15:06:48 / cg"
   446     "Modified: / 25.2.1998 / 19:20:59 / cg"
       
   447 !
       
   448 
       
   449 executeCommandAndShowOutput:cmd
       
   450     |doneSemaphore line p|
       
   451 
       
   452     doneSemaphore := Semaphore new.
       
   453 
       
   454     copyProcess := [   
       
   455 
       
   456         p := PipeStream readingFrom:cmd.
       
   457         p isNil ifTrue:[
       
   458             self warn:('command error. Could not execute:\\' , cmd) withCRs.
       
   459         ] ifFalse:[
       
   460             [
       
   461                 [p atEnd] whileFalse:[
       
   462                     (p readWaitWithTimeout:0.1) ifFalse:[
       
   463                         line := p nextLine.
       
   464                         (line notNil and:[line notEmpty]) ifTrue:[
       
   465                             commandTraceView showCR:(('  ' , line) asText emphasizeAllWith:(#color->Color red)).
       
   466                             commandTraceView endEntry.
       
   467                         ]
       
   468                     ]
       
   469                 ].
       
   470                 p close.
       
   471             ] valueOnUnwindDo:[
       
   472                 p shutDown
       
   473             ]
       
   474         ].
       
   475         doneSemaphore signal.
       
   476         copyProcess := nil.
       
   477     ] forkAt:4.
       
   478 
       
   479     doneSemaphore wait.
       
   480 
       
   481     "Created: / 25.2.1998 / 17:46:06 / cg"
       
   482     "Modified: / 25.2.1998 / 18:36:50 / cg"
   416 !
   483 !
   417 
   484 
   418 outputInitialMessage
   485 outputInitialMessage
   419     #(
   486     #(
   420     'Notice:'
   487     'Notice:'
   463 !STXInstaller methodsFor:'startup'!
   530 !STXInstaller methodsFor:'startup'!
   464 
   531 
   465 askAndInstall
   532 askAndInstall
   466     "/ check, if we are in the projects/smalltalk directory
   533     "/ check, if we are in the projects/smalltalk directory
   467 
   534 
       
   535     |answer|
       
   536 
   468     resources := ResourcePack for:self class.
   537     resources := ResourcePack for:self class.
   469 
   538 
   470     (Filename currentDirectory pathName endsWith:'projects/smalltalk') ifFalse:[
   539     (Filename currentDirectory pathName endsWith:'projects/smalltalk') ifFalse:[
   471         self warn:(resources string:'must be in the ''projects/smalltalk'' directory').
   540         self warn:(resources string:'must be in the ''projects/smalltalk'' directory').
   472         ^ self
   541         ^ self
   473     ].
   542     ].
       
   543 
       
   544     answer := self askForFullInstallation.
       
   545     answer ifFalse:[^ self].
   474 
   546 
   475     [self askForDestination] whileTrue:[
   547     [self askForDestination] whileTrue:[
   476         self checkForExistingInstallationAndConfirm ifTrue:[
   548         self checkForExistingInstallationAndConfirm ifTrue:[
   477             self preInstall.
   549             self preInstall.
   478             self doInstall ifTrue:[
   550             self doInstall ifTrue:[
   484                 ^ self
   556                 ^ self
   485             ]
   557             ]
   486         ]
   558         ]
   487     ].
   559     ].
   488 
   560 
   489     "Modified: 2.3.1997 / 13:46:23 / cg"
   561     "Modified: / 25.2.1998 / 16:54:51 / cg"
   490 !
   562 !
   491 
   563 
   492 askForDestination
   564 askForDestination
   493     "open a dialog to enter destination directories"
   565     "open a dialog to enter destination directories"
   494 
   566 
       
   567     fullInstallation ifTrue:[
       
   568         ^ self askForDestinationForFullInstallation
       
   569     ] ifFalse:[
       
   570         ^ self askForDestinationForPartialInstallation
       
   571     ]
       
   572 
       
   573     "
       
   574      STXInstaller open
       
   575     "
       
   576 
       
   577     "Modified: / 25.2.1998 / 17:12:45 / cg"
       
   578 !
       
   579 
       
   580 askForDestinationForFullInstallation
       
   581     "open a dialog to enter destination directories"
       
   582 
   495     |d cm l green dark img
   583     |d cm l green dark img
   496      stxLibDirHolder stxLibBinDirHolder stxBinDirHolder
   584      fullDirHolder|
   497      installDocHolder installSourceHolder installSTCHolder installGoodiesHolder
   585 
   498      binMegabytes libMegabytes docMegabytes stcMegabytes srcMegabytes
   586     LastFullDir isNil ifTrue:[
   499     |
   587         LastFullDir := (Filename homeDirectory 
   500 
   588                             construct:'stx')
   501     binMegabytes := 10.
   589                             constructString:'develop'
   502     libMegabytes := 30.
   590     ].
   503     docMegabytes := 11.
   591 
   504     stcMegabytes := 1.
   592     fullDirHolder := LastFullDir asValue.
   505     srcMegabytes := 15.
       
   506 
       
   507     LastLibDir isNil ifTrue:[
       
   508         LastLibDir := '/usr/local/lib/smalltalk'
       
   509     ].
       
   510     LastLibBinDir isNil ifTrue:[
       
   511         LastLibBinDir := '/usr/local/lib'
       
   512     ].
       
   513     LastBinDir isNil ifTrue:[
       
   514         LastBinDir := '/usr/local/bin'
       
   515     ].
       
   516 
       
   517     stxLibDirHolder := LastLibDir asValue.
       
   518     stxLibBinDirHolder := LastLibBinDir asValue.
       
   519     stxBinDirHolder := LastBinDir asValue.
       
   520 
       
   521     installDocHolder := true asValue.
       
   522     installSourceHolder := true asValue.
       
   523     installSTCHolder := true asValue.
       
   524     installGoodiesHolder := true asValue.
       
   525 
   593 
   526     Screen current hasColors ifTrue:[
   594     Screen current hasColors ifTrue:[
   527         green := (Color red:0 green:80 blue:20) "darkened".
   595         green := (Color red:0 green:80 blue:20) "darkened".
   528         dark := Color grey:10.
   596         dark := Color grey:10.
   529     ] ifFalse:[
   597     ] ifFalse:[
   531         dark := Color black.
   599         dark := Color black.
   532     ].
   600     ].
   533 
   601 
   534     d := DialogBox new.
   602     d := DialogBox new.
   535 
   603 
   536     d label:(resources string:'ST/X CD Installation').
   604     d label:(resources string:'ST/X Full Installation').
   537     img := Image fromFile:'SmalltalkX.xbm'.
   605     img := Image fromFile:'SmalltalkX.xbm'.
   538 
   606 
   539     l := d addTextLabel:img.
   607     l := d addTextLabel:img.
   540     l adjust:#left; foregroundColor:green backgroundColor:dark.
   608     l adjust:#left; foregroundColor:green backgroundColor:dark.
   541 
   609 
   542     l := d addTextLabel:(resources string:'Smalltalk/X CD installation.').
   610     l := d addTextLabel:(resources string:'Smalltalk/X CD installation (full).').
       
   611     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   612     d addVerticalSpace.
       
   613     d addVerticalSpace.
       
   614 
       
   615     d addHorizontalLine.
       
   616 
       
   617     l := d addTextLabel:(resources string:'ST/X development directory:').
       
   618     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   619 
       
   620     cm := ComboBoxView on:fullDirHolder.
       
   621     cm list:self defaultFullDirs.
       
   622     d 
       
   623         addLabelledField:cm 
       
   624         label:(resources string:'stx develop')
       
   625         adjust:#left 
       
   626         tabable:true 
       
   627         from:0.0 to:1.0 separateAtX:0.25
       
   628         nameAs:'fullBox'.
       
   629 
       
   630     (d componentAt:'fullBox.label') backgroundColor:dark; foregroundColor:Color white.
       
   631 
       
   632     d addVerticalSpace.
       
   633     d addHorizontalLine.
       
   634 
       
   635     d addHelpButtonFor:'STXInstaller/installHelp.html';
       
   636       addAbortButton; 
       
   637       addOkButtonLabelled:(resources string:'install').
       
   638     d extent:500@400.
       
   639 
       
   640     d allViewBackground:dark.
       
   641 
       
   642     d openAtCenter.
       
   643     d accepted ifTrue:[
       
   644         fullDir := LastFullDir := fullDirHolder value.
       
   645         d destroy.
       
   646         ^ true
       
   647     ].
       
   648     d destroy.
       
   649     ^ false
       
   650 
       
   651     "
       
   652      STXInstaller open
       
   653     "
       
   654 
       
   655     "Created: / 25.2.1998 / 17:11:37 / cg"
       
   656     "Modified: / 25.2.1998 / 17:29:07 / cg"
       
   657 !
       
   658 
       
   659 askForDestinationForPartialInstallation
       
   660     "open a dialog to enter destination directories"
       
   661 
       
   662     |d cm l green dark img
       
   663      stxLibDirHolder stxLibBinDirHolder stxBinDirHolder
       
   664      installDocHolder installSourceHolder installSTCHolder installGoodiesHolder
       
   665      binMegabytes libMegabytes docMegabytes stcMegabytes srcMegabytes
       
   666     |
       
   667 
       
   668     binMegabytes := 12.
       
   669     libMegabytes := 30.
       
   670     docMegabytes := 15.
       
   671     stcMegabytes := 1.
       
   672     srcMegabytes := 20.
       
   673 
       
   674     LastLibDir isNil ifTrue:[
       
   675         LastLibDir := '/usr/local/lib/smalltalk'
       
   676     ].
       
   677     LastLibBinDir isNil ifTrue:[
       
   678         LastLibBinDir := '/usr/local/lib'
       
   679     ].
       
   680     LastBinDir isNil ifTrue:[
       
   681         LastBinDir := '/usr/local/bin'
       
   682     ].
       
   683 
       
   684     stxLibDirHolder := LastLibDir asValue.
       
   685     stxLibBinDirHolder := LastLibBinDir asValue.
       
   686     stxBinDirHolder := LastBinDir asValue.
       
   687 
       
   688     installDocHolder := true asValue.
       
   689     installSourceHolder := true asValue.
       
   690     installSTCHolder := true asValue.
       
   691     installGoodiesHolder := true asValue.
       
   692 
       
   693     Screen current hasColors ifTrue:[
       
   694         green := (Color red:0 green:80 blue:20) "darkened".
       
   695         dark := Color grey:10.
       
   696     ] ifFalse:[
       
   697         green := Color white.
       
   698         dark := Color black.
       
   699     ].
       
   700 
       
   701     d := DialogBox new.
       
   702 
       
   703     d label:(resources string:'ST/X Partial Installation').
       
   704     img := Image fromFile:'SmalltalkX.xbm'.
       
   705 
       
   706     l := d addTextLabel:img.
       
   707     l adjust:#left; foregroundColor:green backgroundColor:dark.
       
   708 
       
   709     l := d addTextLabel:(resources string:'Smalltalk/X CD installation (partial).').
   543     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
   710     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
   544     d addVerticalSpace.
   711     d addVerticalSpace.
   545     d addVerticalSpace.
   712     d addVerticalSpace.
   546 
   713 
   547     d addHorizontalLine.
   714     d addHorizontalLine.
   548 
   715 
   549     l := d addTextLabel:(resources string:'Destination directories:').
   716     l := d addTextLabel:(resources string:'Destination directories:').
   550     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
   717     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   718 
       
   719     l := d addTextLabel:(resources string:'(the defaults below are recommended)').
       
   720     l adjust:#right; backgroundColor:dark; foregroundColor:Color white.
   551 
   721 
   552     cm := ComboBoxView on:stxBinDirHolder.
   722     cm := ComboBoxView on:stxBinDirHolder.
   553     cm list:self defaultBinDirs.
   723     cm list:self defaultBinDirs.
   554     d 
   724     d 
   555         addLabelledField:cm 
   725         addLabelledField:cm 
   646         ^ true
   816         ^ true
   647     ].
   817     ].
   648     d destroy.
   818     d destroy.
   649     ^ false
   819     ^ false
   650 
   820 
   651     "Modified: 22.5.1997 / 15:04:29 / cg"
   821     "
       
   822      STXInstaller open
       
   823     "
       
   824 
       
   825     "Created: / 25.2.1998 / 17:11:26 / cg"
       
   826     "Modified: / 25.2.1998 / 19:43:30 / cg"
       
   827 !
       
   828 
       
   829 askForFullInstallation
       
   830     "open a dialog to enter destination directories"
       
   831 
       
   832     |d cm l green dark img|
       
   833 
       
   834     Screen current hasColors ifTrue:[
       
   835         green := (Color red:0 green:80 blue:20) "darkened".
       
   836         dark := Color grey:10.
       
   837     ] ifFalse:[
       
   838         green := Color white.
       
   839         dark := Color black.
       
   840     ].
       
   841 
       
   842     d := DialogBox new.
       
   843 
       
   844     d label:(resources string:'ST/X CD Installation').
       
   845     img := Image fromFile:'SmalltalkX.xbm'.
       
   846 
       
   847     l := d addTextLabel:img.
       
   848     l adjust:#left; foregroundColor:green backgroundColor:dark.
       
   849 
       
   850     l := d addTextLabel:(resources string:'Smalltalk/X CD installation.').
       
   851     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   852     d addVerticalSpace.
       
   853     d addVerticalSpace.
       
   854 
       
   855     d addHorizontalLine.
       
   856 
       
   857     l := d addTextLabel:(resources string:
       
   858 'You can either perform a ' , 'full' asText allBold , ' installation, or a ' , 'partial' asText allBold ,' installation.').
       
   859     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   860 
       
   861     d addVerticalSpace.
       
   862     d addHorizontalLine.
       
   863 
       
   864     d leftIndent:20.
       
   865     l := d addTextLabel:(resources string:
       
   866 'The full installation is required if you want to build your own
       
   867 customized smalltalk executable. It allows you to include additional 
       
   868 precompiled classes or classLibraries. 
       
   869 This is also required if you want to link your own standalone executables.
       
   870 
       
   871 It consists of a directory hierachy, including makefiles for a customizeable 
       
   872 rebuild of the whole smalltalk system.
       
   873 (Actually, it simply copies the whole CD contents onto your disk).
       
   874 This requires roughly 120-200Mb of hard disk space.').
       
   875     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   876 
       
   877     d addVerticalSpace.
       
   878     d addHorizontalLine.
       
   879 
       
   880     l := d addTextLabel:(resources string:
       
   881 'The partial installation requires less disk space and only copies the
       
   882 smalltalk executable, shared libraries and support files onto your hard disk.
       
   883 This requires roughly 70-90Mb of hard disk space.
       
   884 
       
   885 
       
   886  ').
       
   887     l adjust:#left; backgroundColor:dark; foregroundColor:Color white.
       
   888 
       
   889 
       
   890     d leftIndent:0.
       
   891     d addVerticalSpace.
       
   892     d addHorizontalLine.
       
   893 
       
   894 
       
   895     d addHelpButtonFor:'STXInstaller/installHelp.html';
       
   896       addAbortButton; 
       
   897       addOkButton:(Button label:(resources string:'install full') action:[fullInstallation:=true]);
       
   898       addOkButtonLabelled:(resources string:'install partial').
       
   899     d extent:500@400.
       
   900 
       
   901     d allViewBackground:dark.
       
   902 
       
   903     fullInstallation := false.
       
   904     d openAtCenter.
       
   905     d accepted ifTrue:[
       
   906         d destroy.
       
   907         ^ true
       
   908     ].
       
   909     d destroy.
       
   910     ^ false
       
   911 
       
   912     "
       
   913      STXInstaller open
       
   914     "
       
   915 
       
   916     "Created: / 25.2.1998 / 16:50:16 / cg"
       
   917     "Modified: / 25.2.1998 / 19:42:31 / cg"
   652 !
   918 !
   653 
   919 
   654 checkForExistingInstallationAndConfirm
   920 checkForExistingInstallationAndConfirm
   655     "look if there is another installation and confirm
   921     "look if there is another installation and confirm
   656      reinstalling; return true if ok, false if not"
   922      reinstalling; return true if ok, false if not"
   657 
   923 
   658     |whatToDo|
   924     |whichDir canOverWrite whatToDo box|
   659 
   925 
   660     stxLibDir asFilename exists ifTrue:[
   926     fullInstallation ifTrue:[
   661         whatToDo := Dialog 
   927         whichDir := fullDir.
   662                         choose:(resources 
   928         canOverWrite := false.
   663                                     string:'detected existing ST/X installation in %1' 
   929     ] ifFalse:[
   664                                       with:stxLibDir asText allBold)
   930         whichDir := stxLibDir.
   665                         label:(resources string:'Attention')
   931         canOverWrite := true.
   666                         labels:(resources array:#('remove first' 'overwrite' 'cancel')) 
   932     ].
   667                         values:#(remove over nil) 
   933 
   668                         default:nil.     
   934     whichDir asFilename exists ifTrue:[
   669 
   935             whatToDo := Dialog 
   670         whatToDo isNil ifTrue:[^false].
   936                             choose:(resources 
   671         whatToDo == #remove ifTrue:[
   937                                         string:'detected existing ST/X installation in %1' 
   672             ((stxLibDir findString:'stx') == 0
   938                                           with:whichDir asText allBold)
   673             and:[(stxLibDir findString:'smalltalk') == 0]) ifTrue:[
   939                             label:(resources string:'Attention')
   674                 "/ confirm again
   940                             labels:(resources array:(canOverWrite 
   675                 (self confirm:(resources 
   941                                                     ifFalse:[#('remove first' 'cancel')] 
   676                                 string:'are you certain that the directory to remove
   942                                                     ifTrue:[#('remove first' 'overwrite' 'cancel')] )) 
   677 (' , stxLibDir , ') is really a smalltalk directory ?
   943                             values:(canOverWrite ifFalse:[#(remove nil)] ifTrue:[#(remove over nil)])
       
   944                             default:nil.     
       
   945 
       
   946             whatToDo isNil ifTrue:[^false].
       
   947             whatToDo == #remove ifTrue:[
       
   948                 ((whichDir findString:'stx') == 0
       
   949                 and:[(whichDir findString:'smalltalk') == 0]) ifTrue:[
       
   950                     "/ confirm again
       
   951                     (self confirm:(resources 
       
   952                                     string:'are you certain that the directory to remove
       
   953 (' , whichDir , ') is really a smalltalk directory ?
   678 
   954 
   679 Remove it now ?')) ifFalse:[ 
   955 Remove it now ?')) ifFalse:[ 
   680                     (self confirm:(resources 
   956                         ^ false
   681                                      string:'overwrite ?')) ifTrue:[^ true].
   957                     ]
       
   958                 ].
       
   959 
       
   960                 [
       
   961                     box := DialogBox new label:'please wait'.
       
   962                     box addTextLabel:'removing ' , whichDir , ' ...'.
       
   963                     box showAtPointer.
       
   964                 ] forkAt:(Processor activePriority+1).
       
   965                 box waitUntilVisible.
       
   966 
       
   967                 (OperatingSystem recursiveRemoveDirectory:whichDir)
       
   968                 ifFalse:[
       
   969                     self warn:(resources string:'mhmh - could not remove old installation.
       
   970 
       
   971 Please remove it manually (using root privileges if required) 
       
   972 and try again.').
       
   973                     box destroy.
   682                     ^ false
   974                     ^ false
   683                 ]
   975                 ].
       
   976 
       
   977                 box destroy
   684             ].
   978             ].
   685 
   979     ].
   686             (OperatingSystem recursiveRemoveDirectory:stxLibDir)
   980 
   687             ifFalse:[
       
   688                 self warn:(resources string:'mhmh - could not remove old installation.')
       
   689             ].
       
   690         ].
       
   691         ^ true
       
   692     ].
       
   693     ^ true
   981     ^ true
   694 
   982 
   695     "Modified: 2.3.1997 / 13:45:13 / cg"
   983     "
       
   984      STXInstaller open
       
   985     "
       
   986 
       
   987     "Modified: / 25.2.1998 / 19:35:12 / cg"
   696 !
   988 !
   697 
   989 
   698 doInstall
   990 doInstall
   699     "install ST/X; return true if ok, false if not"
   991     "install ST/X; return true if ok, false if not"
   700 
   992 
   701     |progressView ok textView|
   993     |progressView ok v textView p l 
   702 
   994      dirToMonitor doDfMonitoring dfMonitorProcess|
   703     textView := HVScrollableView for:TextCollector.
   995 
   704     textView preferredExtent:(200 @ 300).
   996     doDfMonitoring := false.
       
   997 
       
   998     v := View new preferredExtent:(250 @ 350).
       
   999 
       
  1000     textView := HVScrollableView for:TextCollector in:v.
       
  1001     textView origin:0.0@0.0 corner:1.0@1.0.
       
  1002     textView bottomInset:30.
   705     commandTraceView := textView scrolledView.
  1003     commandTraceView := textView scrolledView.
       
  1004 
       
  1005     fullInstallation ifTrue:[
       
  1006         dirToMonitor := fullDir.
       
  1007     ] ifFalse:[
       
  1008         dirToMonitor := stxLibDir
       
  1009     ].
       
  1010 
       
  1011     (OperatingSystem canExecuteCommand:'df ' , dirToMonitor) ifTrue:[
       
  1012         p := HorizontalPanelView in:v.
       
  1013         p origin:0.0@1.0 corner:1.0@1.0.
       
  1014         p topInset:-30.
       
  1015         p horizontalLayout:#fit.
       
  1016 
       
  1017         l := Label label:'' in:p.
       
  1018         l labelChannel:(dfHolder := '' asValue).
       
  1019         l adjust:#left.
       
  1020         dfMonitorProcess := [
       
  1021             |ok p text keys values i l|
       
  1022 
       
  1023             ok := true.
       
  1024             [ok] whileTrue:[
       
  1025                 doDfMonitoring ifTrue:[
       
  1026                     ok := false.
       
  1027                     p := PipeStream readingFrom:('df -k ' , dirToMonitor).
       
  1028                     p notNil ifTrue:[
       
  1029                        [
       
  1030                            text := p contentsOfEntireFile.
       
  1031                        ] valueNowOrOnUnwindDo:[
       
  1032                            p close.
       
  1033                        ].
       
  1034 "/ Transcript showCR:text asString.
       
  1035                        text notNil ifTrue:[
       
  1036                            text := text asCollectionOfLines.
       
  1037                            text size >= 2 ifTrue:[
       
  1038                                keys := (text at:1) asCollectionOfWords.
       
  1039                                values := (text at:2) asCollectionOfWords.
       
  1040                                i := (keys indexOf:'Capacity').
       
  1041                                i == 0 ifTrue:[
       
  1042                                    i := (keys indexOf:'capacity').
       
  1043                                ].
       
  1044                                i ~~ 0 ifTrue:[
       
  1045                                    l := 'Used disk space: ' , (values at:i) withoutSeparators.
       
  1046                                    i := (keys indexOf:'Available').
       
  1047                                    i == 0 ifTrue:[
       
  1048                                        i := (keys indexOf:'available').
       
  1049                                        i == 0 ifTrue:[
       
  1050                                            i := (keys indexOf:'avail').
       
  1051                                            i == 0 ifTrue:[
       
  1052                                                i := (keys indexOf:'Avail').
       
  1053                                            ].
       
  1054                                        ].
       
  1055                                    ].
       
  1056                                    i ~~ 0 ifTrue:[
       
  1057                                         l := l , ' (' , (values at:i) withoutSeparators , 'k available)'.
       
  1058                                    ].
       
  1059                                    dfHolder value:l.
       
  1060                                    ok := true.
       
  1061                                    Delay waitForSeconds:9.
       
  1062                                ]
       
  1063                            ]
       
  1064                         ].
       
  1065                     ].
       
  1066                 ].
       
  1067                 Delay waitForSeconds:1.
       
  1068             ]
       
  1069         ] forkAt:(Processor activePriority+3)
       
  1070     ].
   706 
  1071 
   707     progressView := ProgressIndicator
  1072     progressView := ProgressIndicator
   708                         inBoxWithLabel:'ST/X Installation' icon:(Depth8Image fromImage:Launcher aboutIcon)
  1073                         inBoxWithLabel:'ST/X Installation' icon:(Depth8Image fromImage:Launcher aboutIcon)
   709                         text:#('ST/X Installation' '' '' '' '' '' '' '') asStringCollection
  1074                         text:#('ST/X Installation' '' '' '' '' '' '' '') asStringCollection
   710                         abortable:true
  1075                         abortable:true
   711                         view:textView
  1076                         view:v
   712                         closeWhenDone:false.
  1077                         closeWhenDone:false.
   713     progressView topView extent:(640 min:Display width) @ (500 min:Display height).
  1078     progressView topView extent:(640 min:Display width) @ (500 min:Display height).
   714 
  1079 
   715     ok := false.
  1080     ok := false.
   716 
  1081 
   719 
  1084 
   720               Processor activeProcess withPriority:7 do:[
  1085               Processor activeProcess withPriority:7 do:[
   721                   actionPercentageHolder := progressValue.
  1086                   actionPercentageHolder := progressValue.
   722                   actionTextHolder := currentAction.
  1087                   actionTextHolder := currentAction.
   723 
  1088 
   724                   self outputInitialMessage.
  1089                   fullInstallation ifFalse:[
       
  1090                         self outputInitialMessage.
       
  1091                   ].
   725 
  1092 
   726                   (self createDirectories) ifTrue:[
  1093                   (self createDirectories) ifTrue:[
       
  1094                       doDfMonitoring := true.
   727                       ok := self copyFiles
  1095                       ok := self copyFiles
   728                   ].
  1096                   ].
   729                   self createSymbolicLinks.
  1097                   self createSymbolicLinks.
   730 
  1098 
   731                   progressValue value:100.
  1099                   progressValue value:100.
   738                   actionTextHolder value:nil.
  1106                   actionTextHolder value:nil.
   739                   actionTextHolder value:msg.
  1107                   actionTextHolder value:msg.
   740               ] 
  1108               ] 
   741             ].
  1109             ].
   742 
  1110 
       
  1111     dfMonitorProcess notNil ifTrue:[
       
  1112         dfMonitorProcess terminate
       
  1113     ].
       
  1114     copyProcess notNil ifTrue:[
       
  1115         copyProcess terminate.
       
  1116         copyProcess := nil.
       
  1117     ].
   743     ^ ok
  1118     ^ ok
   744 
  1119 
   745     "Created: 17.7.1996 / 15:11:27 / cg"
  1120     "
   746     "Modified: 2.3.1997 / 12:59:47 / cg"
  1121      STXInstaller open
       
  1122     "
       
  1123 
       
  1124     "Created: / 17.7.1996 / 15:11:27 / cg"
       
  1125     "Modified: / 25.2.1998 / 19:36:08 / cg"
   747 !
  1126 !
   748 
  1127 
   749 open
  1128 open
   750     self askAndInstall.
  1129     self askAndInstall.
   751 
  1130 
   756 
  1135 
   757 postInstall
  1136 postInstall
   758     "some messages at the end ..."
  1137     "some messages at the end ..."
   759 
  1138 
   760     |shInfo cshInfo msg havePath|
  1139     |shInfo cshInfo msg havePath|
       
  1140 
       
  1141     resources isNil ifTrue:[
       
  1142         resources := ResourcePack for:self class.
       
  1143     ].
   761 
  1144 
   762     msg := (resources string:'ST/X Installation complete.\\') withCRs.
  1145     msg := (resources string:'ST/X Installation complete.\\') withCRs.
   763     shInfo := ''.
  1146     shInfo := ''.
   764     cshInfo := ''.
  1147     cshInfo := ''.
   765 
  1148 
   766     havePath := true.
  1149     fullInstallation ifTrue:[
   767     (((OperatingSystem getEnvironment:'PATH')
  1150         msg := msg , 'You will now find a development directory hierarchy
   768         asCollectionOfSubstringsSeparatedBy:$:)
  1151 in ''' , fullDir asText allBold , '''.
   769             includes:stxBinDir) ifFalse:[
  1152 
   770 
  1153 To try it, ''cd'' to ''' , fullDir , '/projects/smalltalk''
   771         havePath := false.
  1154 and start smalltalk with the command: ''./smalltalk''.
   772         shInfo  := 'PATH=$PATH:' , stxBinDir , ' ; export PATH\'.
  1155 
   773         cshInfo := 'set path=($path ' , stxBinDir , ')\'.
  1156 To perform a partial installation of your customized smalltalk later,
   774         msg := msg , (resources string:'%1 is not in your PATH.\You should change your ".login" and/or ".profile" files to include it.\\'
  1157 use the INSTALL script found in ''' , fullDir , ''''.
   775                                   with:stxBinDir asText allBold) withCRs.
  1158 
   776     ].
  1159     ] ifFalse:[
   777 
  1160         havePath := true.
   778     (stxLibDir ~= '/usr/local/lib/smalltalk'
  1161         (((OperatingSystem getEnvironment:'PATH')
   779     and:[stxLibDir ~= '/usr/lib/smalltalk']) ifTrue:[
  1162             asCollectionOfSubstringsSeparatedBy:$:)
   780         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.\'
  1163                 includes:stxBinDir) ifFalse:[
   781                                   with:'STX_LIBDIR' asText allBold 
  1164 
   782                                   with:stxLibDir asText allBold) withCRs.
  1165             havePath := false.
   783         havePath ifFalse:[
  1166             shInfo  := 'PATH=$PATH:' , stxBinDir , ' ; export PATH\'.
   784             msg := msg , (resources string:'The above mentioned files are also a good place to do this.\') withCRs.
  1167             cshInfo := 'set path=($path ' , stxBinDir , ')\'.
   785         ] ifTrue:[
  1168             msg := msg , (resources string:'%1 is not in your PATH.\You should change your ".login" and/or ".profile" files to include it.\\'
   786             msg := msg , (resources string:'The ".login" and/or ".profile" files are a good place to do this.\') withCRs.
  1169                                       with:stxBinDir asText allBold) withCRs.
   787         ].
  1170         ].
   788 
  1171 
   789         shInfo := shInfo , 'STX_LIBDIR=' , stxLibDir , ' ; export STX_LIBDIR\'.
  1172         (stxLibDir ~= '/usr/local/lib/smalltalk'
   790         cshInfo := cshInfo , 'setenv STX_LIBDIR ' , stxLibDir , '\'.
  1173         and:[stxLibDir ~= '/usr/lib/smalltalk']) ifTrue:[
   791     ].
  1174             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.\'
   792 
  1175                                       with:'STX_LIBDIR' asText allBold 
   793     shInfo notEmpty ifTrue:[
  1176                                       with:stxLibDir asText allBold) withCRs.
   794         '*********************************************************' errorPrintCR.
  1177             havePath ifFalse:[
   795         (resources string:'Message from the ST/X Installer:\\') withCRs errorPrintCR.
  1178                 msg := msg , (resources string:'The above mentioned files are also a good place to do this.\') withCRs.
   796         (resources string:'Please add the following to your ".profile" file:') withCRs errorPrintCR.
  1179             ] ifTrue:[
   797         '' errorPrintCR.
  1180                 msg := msg , (resources string:'The ".login" and/or ".profile" files are a good place to do this.\') withCRs.
   798         shInfo withCRs errorPrintCR.
  1181             ].
   799         '' errorPrintCR.
  1182 
   800         (resources string:'or (if you use csh/tcsh), add to your ".login" file:') withCRs errorPrintCR.
  1183             shInfo := shInfo , 'STX_LIBDIR=' , stxLibDir , ' ; export STX_LIBDIR\'.
   801         '' errorPrintCR.
  1184             cshInfo := cshInfo , 'setenv STX_LIBDIR ' , stxLibDir , '\'.
   802         cshInfo withCRs errorPrintCR.
  1185         ].
   803         '' errorPrintCR.
  1186 
   804         '*********************************************************' errorPrintCR.
  1187         shInfo notEmpty ifTrue:[
       
  1188             '*********************************************************' errorPrintCR.
       
  1189             (resources string:'Message from the ST/X Installer:\\') withCRs errorPrintCR.
       
  1190             (resources string:'Please add the following to your ".profile" file:') withCRs errorPrintCR.
       
  1191             '' errorPrintCR.
       
  1192             shInfo withCRs errorPrintCR.
       
  1193             '' errorPrintCR.
       
  1194             (resources string:'or (if you use csh/tcsh), add to your ".login" file:') withCRs errorPrintCR.
       
  1195             '' errorPrintCR.
       
  1196             cshInfo withCRs errorPrintCR.
       
  1197             '' errorPrintCR.
       
  1198             '*********************************************************' errorPrintCR.
       
  1199         ].
   805     ].
  1200     ].
   806 
  1201 
   807     msg := msg , '\\Have fun using ST/X !!'.
  1202     msg := msg , '\\Have fun using ST/X !!'.
   808 
  1203 
   809     self information:msg withCRs.
  1204     self information:msg withCRs.
   810 
  1205 
   811     "
  1206     "Modified: / 25.2.1998 / 19:29:04 / cg"
   812      STXInstaller new postInstall
       
   813     "
       
   814 
       
   815     "Modified: 2.3.1997 / 13:28:18 / cg"
       
   816 !
  1207 !
   817 
  1208 
   818 preInstall
  1209 preInstall
   819     "clobber the doc directory, to avoid copying cyclic symbolic links"
  1210     "clobber the doc directory, to avoid copying cyclic symbolic links.
       
  1211      Notice, the CD does not contain symlinks, but checking for them
       
  1212      allows installing from a development dir."
   820 
  1213 
   821     |f|
  1214     |f|
   822 
  1215 
   823     f := '../../doc/online/english/german' asFilename.
  1216     f := '../../doc/online/english/german' asFilename.
   824     f exists ifTrue:[
  1217     f exists ifTrue:[
   829 
  1222 
   830     "
  1223     "
   831      STXInstaller new preInstall
  1224      STXInstaller new preInstall
   832     "
  1225     "
   833 
  1226 
   834     "Modified: 18.7.1996 / 22:10:42 / cg"
  1227     "Modified: / 25.2.1998 / 17:39:55 / cg"
   835 ! !
  1228 ! !
   836 
  1229 
   837 !STXInstaller class methodsFor:'documentation'!
  1230 !STXInstaller class methodsFor:'documentation'!
   838 
  1231 
   839 version
  1232 version