Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
SARInstaller
Last updated at 3:49 am UTC on 22 March 2018

About SAR files

As part of the SqueakMap project, we've come up with a convention for structuring multi-file Squeak archives. We're using the .sar (Squeak ARchive) extension for these. SARS are simply ZipArchives that can have any content and that can be used to install code in an image. If you have a Squeak package that requires more than one file, you should consider distributing it as a SAR.

There are two special (reserved) member names in a .sar file:
The preamble and postscript members themselves are filed in as Smalltalk code and must be in Smalltalk chunk format.

Installing a SAR file

(For years no one thought of putting a section here on how to install a SAR file? ... here it is, you're welcome :)
Squeak can install a SAR file directly from its internal SqueakMap browser, its internal File Tool (browse to the file and an install button will appear), or by dragging a SAR file from the underlying OS's file-manager on to a running Squeak image.

About SARInstaller

SARInstaller is a package that knows how to load SAR (Squeak ARchive) files by executing the statements in the preamble and/or postscript member(s). Within the preamble and postscript, self stands for the SARInstaller that's loading the archive. Here's how to load different types of SAR members from a preamble or postscript member:
For this SAR Member type,install using:
Change setsself fileInMemberNamed: 'member.cs'
DVS packagesself fileInPackageNamed: 'member.st'
Monticello packages (.mc)self fileInMonticelloPackageNamed: 'member.mc'
Monticello versions (.mcv)self fileInMonticelloVersionNamed: 'member.mcv'
Monticello versions (.mcz)self fileInMonticelloZipVersionNamed: 'member.mcz'
Projects (with construction of a ViewMorph)self fileInProjectNamed: 'member.pr' createView: true
Projects (without construction of a ViewMorph)self fileInProjectNamed: 'member.pr' createView: false
Genie gesture dictionariesself fileInGenieDictionaryNamed: 'member.ggd'
Graphics files (.gif, .jpg, .form, etc.) (loaded as SketchMorphs)self openGraphicsFile: 'member.jpg'
Text files (loaded as text editor windows)self openTextFile: 'member.text'
TrueType fontsself fileInTrueTypeFontNamed: 'member.ttf'
Morph(s) in filesself fileInMorphsNamed: 'member.morph' addToWorld: true

Arbitrary files can be extracted in various ways:
Extract member and write to file,using:
using member name as a filenameself extractMember: 'member.xxx'
specifying a different filenameself extractMember: 'member.xxx' toFileNamed: 'newName'
using member name as a filename but stripping the directoriesself extractMemberWithoutPath: 'member.xxx'
using member name as a filename but stripping the directories and specifying a different directoryself extractMemberWithoutPath: 'member.xxx' inDirectory: 'directoryName'

And if the above built in options aren't enough, you can get to the ZipArchive or its members directly from the preamble or postscript:
    self zip ...
    self memberNamed: 'memberName' ...
    (self memberNamed: 'memberName') contentStream ...
This gives you complete flexibility over how to do an install.

Getting SARInstaller

3.6 and later images include the SARInstaller package. Or you can get v21 here: SARInstallerFor36-nk.cs.gz or v16 has here: SARInstallerFor34-nk.cs.gz. You can get SARInstaller for 3.4 and 3.5 images from SqueakMap and the SARInstaller for 3.2 images from SqueakMap

Creating a SAR file

For the impatient, there is a short SAR Building Cookbook.
To distribute your package using a SAR file, you can a) manually use some Zip tool such as the ArchiveViewer, b) use the SARBuilder, or c) use DVS packages. First, remember you don't need SAR files if your package is "just code". If the package contains other files/resources then SAR is appropriate.

Here's how to use ZipArchive to create a SAR for a package from a set of files:
	zip := ZipArchive new. 
	(zip addFile: 'package-cache/BFAV-nk.122.mcz' as: 'BFAV.mcz') 
            desiredCompressionLevel: 0. 
	zip addString: 'self fileInMonticelloZipVersionNamed: ''BFAV.mcz''.' 
           as: 'install/preamble'.
	zip writeToFileNamed: 'myNewSar.sar'
Here's how to do the same thing by writing the Monticello working version directly into the ZipArchive:
	zip := ZipArchive new. 
	mczStream := RWBinaryOrTextStream on: (String new: 10000). 
	workingCopy := MCWorkingCopy forPackage: (MCPackage new name: 'BFAV'). 
	version := workingCopy newVersion. 
	version fileOutOn: mczStream.
	(zip addString: mczStream contents as: 'BFAV.mcz') 
            desiredCompressionLevel: 0. 
	zip addString: 'self fileInMonticelloZipVersionNamed: ''BFAV.mcz''.' 
           as: 'install/preamble'. 
	zip writeToFileNamed: 'myNewSar2.sar'

Creating a more complex SAR file

On 10 February 2004, Steven Swerling wrote: Could somebody point me to a sample SAR file that might be considered by SqueakMap/SAR/Monticello gurus to be a canonical, good example of a SAR that:
1. Provides a preamble with dependencies loaded at user request.
2. Loads in a Monticello file (instead of putting a 'mypackage.st' file in the SAR, puts a 'mypackage.mcz' file in instead)

Ned Konz replied: My most ambitious SAR file to date is one that I put together to load a demo image. Unfortunately, it's 2.5Mb, but I can describe how it works. Archive: /home/ned/Squeak/OOPSLA/demo.sar contains the following files including change sets, Monticello versions, fonts, gifs, etc:
 	RemoveWorldsOfSqueak-nk.1.cs
 	ActionSequenceFix-nk.3.cs
 	..etc..
 	SARInstaller-nk.27.mcz
 	CustomEvents-nk.13.mcz
 	Plot-nk.4.mcz
 	..etc..
 	fonts/ARROWS1.TTF
 	fonts/ARROWS2.TTF
 	..etc..
 	icons/broom.gif
 	icons/colorize.gif
 	..etc..
 	AlanAll.ggd
 	install/postscript
 	demo.prefs
        ..etc..
 	install/preamble

The install/preamble member contains:
       HandMorph allSubInstances do: [:each |
             each disableGenie.
             each instVarNamed: #genieGestureProcessor put: nil]. !
  
       self extractMember: 'demo.prefs'.
       Preferences loadPreferencesFrom: 'demo.prefs'.  !
 
       (self membersMatching: 'SARInstaller*.mcz') do: [ :m |
            self fileInMonticelloZipVersionNamed: m.
             self zip removeMember: m ]. !   

       { 'RemoveWorldsOfSqueak-nk.*.cs'.
         'MorphRemovalNotificationsFix-nk.*.cs'.
           ..etc..
         'ImportantFixes.*.cs'.
       } do: [ :f | self installMember: f ]. !   
       { 'Refactory*.mcz'.
         'SARInstaller*.mcz'.
         ..etc..
         'EToySimulation*.mcz' 
       } do: [ :f | self installMember: f ]. !   
   
       { 'fonts/arial.ttf'.
         'fonts/arialbd.ttf'.	
         ..etc..
         'fonts/wingding.ttf'. 
       } do: [ :f | self fileInTrueTypeFontNamed: f ]. !   
  
       (self membersMatching: 'icons/*.gif') 
         do: [ :f | self extractMember: f ]. !   
  
       (self membersMatching: 'images/*') 
         do: [ :f | self importImage: f ]. !   
  
       self fileInGenieDictionaryNamed: 'AlanAll.ggd'.

The install/postscript member contains:
  (TextStyle named: 'Tahoma') addNewFontSize: 12; addNewFontSize: 15.
    (TextStyle named: 'Arial') addNewFontSize: 12; addNewFontSize: 15.
    (CRDictionary name: #AlanAll) exportedName: #AlanAll.
  ...etc....
    (CRDictionary name: #NumbersOnly) exportedName: #UpdatingStringMorph.
    !
  
    | style pointSizes texts flap |
     style _ (TextStyle named: 'Arial') copy.
     style fonts withIndexDo: [ :font :index | style fontAt: index put: 
           (font emphasis: 1) ].
  
     texts _ OrderedCollection new.
     style fonts withIndexDo: [ :font :i | | t |
       t _ NCGrabbableDisplayTextMorph  new
            backgroundColor: Color transparent;
            textColor: (Color r: 0.839 g: 0.323 b: 0.0);
            setTextStyle: style;
            contentsAsIs: ('abc' asText addAttribute: (TextFontChange fontNumber: i); 
            yourself);
            setNameTo: 'Text';
            hasDropShadow: true;
            shadowColor: (TranslucentColor r: 0.29 g: 0.29 b: 0.29 alpha: 0.322);
            shadowOffset: 2 at 2;
            yourself.
       t text addAttribute: (TextFontChange fontNumber: i).
        texts add: t.
      ].
  
     flap _ Flaps globalFlapTabWithID: 'Prototypes'.
     flap ifNil: [
         flap _ (Flaps newFlapTitled: 'Prototypes' onEdge: #left) openInWorld.
         Flaps addGlobalFlap: flap.
         Flaps enableGlobalFlaps
     ].
     World addMorph: flap.
     flap _ flap referent.

     texts do: [ :t | flap addMorphBack: t ].

     flap addMorphBack: (RectangleMorph new
          extent: ( 968.0 at 22.0);
          setNameTo: 'Rectangle';
          shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.153);
          shadowOffset: 3 at 3;
          hasDropShadow: true;
          setProperty: #noGestureResize toValue: true;
          borderWidth: 0;
          fillStyle: ((GradientFillStyle ramp: 
              {0.0->(Color r: 0.935 g: 0.548 b: 0.0). 
               1.0-(Color r: 0.935 g: 0.935 b: 0.935)}) 
          origin: 436.0 at 74.0;
          direction: 513 at 3;
          normal: -70 at 149;
          radial: false);
          yourself).

     flap
          layoutPolicy: TableLayout new;
          listCentering: #topLeft;
          setProperty: #alwaysShowThumbnail toValue: true;
          setProperty: #thumbnailHeight toValue: 100;
          setPartsBinStatusTo: true;
          updateSubmorphThumbnails. 
      !

      Preferences setPreference: #displayUnrecognizedGestures toValue: true.
      Preferences setPreference: #showDragControllerFeedback  toValue: false.
      Preferences setPreference: #showGenieFocusRectangle toValue: true.
      World activeHand enableGenie.

     Display newDepth: 32.
     Preferences setPreference: #soundsEnabled toValue: false.
     !   

Steven Swerling If you build SAR files like the above, could you point me to the script or describe the methodology used to create it? Or just chime in with a tip on the best way? Can PackageInfo be told to use an MC file instead of using it's "native" ability to include a changeset for the package?
Ned Konz I used the StarBrowser to collect the bits and pieces that make up the SAR (files, changesets, MC packages, whatever). I have a StarBrowser extension that uses my SARBuilder to make the SAR. I hand-edited the install/preamble and install/postscript to avoid referring to specific versions.

Steven SwerlingAlso, I'd like to provide a good 'unload' procedure. My guess is that the best way to do this is to have Monticello unload it, and also to somewhere override the #removeFromSystem method to do all the unregistering and severing of pointers and dependencies. Is this the best way?
Ned Konz I think the MC unload is the best bet. I'd put class-specific cleanup in the class.

SARS within SARS

Question: Raymond Asselin March 26, 2004 Can a SAR file contain other sarfiles with their own preamble and postscript members? For example, say I have a SarFile named: MyImage, which builds an image with all the facilities I want from a BasicImage. Can I put the AccuFonts.sar in this MyImage.sar or must I pick each individual element of the AccuFonts.sar?
Answer: Ned Konz Sure you can. However, a couple of things you should note:
	self extractMember: 'AccuFonts.sar'.
	SARInstaller installSAR: 'AccuFonts.sar'.
	FileDirectory default deleteFileNamed: 'AccuFonts.sar'.
	SARInstaller new
	    directory: FileDirectory default;
	    fileInFrom: ((self memberNamed: 'AccuFonts.sar') contentStream).
	mySar := ZipArchive new.
	member := mySar addFile: 'AccuFonts.sar'.
	member desiredCompressionLevel: 0.
    (SMSqueakMap default packageWithName: 'AccuFonts') ifNotNilDo: [ :pkg |
       (pkg installedVersion isNil 
          or: [ pkg installedVersion asVersion  '6' asVersion ])ifTrue: 
        [ SMSqueakMap default installPackageLatestPublishedNamed: 'AccuFonts']].
    sar1 := ZipArchive new.
    sar1 addString: 'self inform: ''SAR1, member1.st''.!' 
         as: 'member1.st'. 
    sar1 addString: 'self =fileInMemberNamed: ''member1.st''.' 
         as: 'install/preamble'.
    sar1Stream := RWBinaryOrTextStream on: (ByteArray new: 1000). 
    sar1 writeTo: sar1Stream.
    sar2 := ZipArchive new.
    sar2 addString: 'self inform: ''SAR2, member2.st''.!' 
        as: 'member2.st'. 
    sar2 addString: sar1Stream reset contents 
         as: 'member3.sar'. 
    sar2 addString: 'self fileInMemberNamed: ''member2.st''. 
    SARInstaller new directory: FileDirectory default; 
     fileInFrom: ((self memberNamed: ''member3.sar'') contentStream).'
     as: 'install/preamble'.
    sar2 writeTo: (FileStream newFileNamed: 'test2.sar').
    SARInstaller installSAR: 'test2.sar'