[Pkg] Installer: Installer-Core-kph.298.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Mon Feb 23 03:22:14 UTC 2009


A new version of Installer-Core was added to project Installer:
http://www.squeaksource.com/Installer/Installer-Core-kph.298.mcz

==================== Summary ====================

Name: Installer-Core-kph.298
Author: kph
Time: 23 February 2009, 3:22:02 am
UUID: 23775f6c-0159-11de-8efb-000a95edb42a
Ancestors: Installer-Core-kph.297

+ Migrated LPF scripts from installer.pbwiki to InstallerScripts

=============== Diff against Installer-Core-kph.297 ===============

Item was added:
+ ----- Method: Installer class>>scripts (in category 'internal scripts') -----
+ scripts
+ 
+ 	^ InstallerScripts new!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak38 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak38
+ 
+ Installer debug mantis fixBug: '6476 Enable MC File in if before 3.9'.
+ 
+ Installer install:'LevelPlayingField-Monticello15'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptOmniBrowser (in category 'as yet unclassified') -----
+ scriptOmniBrowser
+ 
+ Installer mantis fixBug: 7132.
+ Installer wiresong project: 'ob';
+ install: 'OmniBrowser-mtf.413';
+ install: 'OB-Standard';
+ install: 'OB-Morphic';
+ install: 'OB-SUnitIntegration';
+ install: 'OB-Enhancements'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSophie (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSophie
+ 
+ 	^ self scriptLevelPlayingFieldSqueak38!

Item was changed:
  ----- Method: Installer class>>do: (in category 'launcher support') -----
  do: webPageName
  
  	| rs |
- 	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
  	rs := webPageName readStream.
  	[ rs atEnd ] whileFalse: [ self install: (rs upTo: $;) ].
  !

Item was added:
+ ----- Method: InstallerScripts>>scriptPackagesPharo (in category 'as yet unclassified') -----
+ scriptPackagesPharo
+ 
+ Installer mantis ensureFix: '7272 BlockContext equality testing missing'.
+ Installer squeaksource project: 'Sake'; install: 'Sake-Core'.
+ Installer squeaksource project: 'Packages';
+ install: 'Sake-Packages';
+ install: 'Packages-Library'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldPreamble (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldPreamble
+ 
+ Transcript show: 'Preamble found:'.
+ Installer mantis ensureFix: 7131.
+ Installer mantis ensureFix: 7205.
+ Installer mantis ensureFix: 7218.
+ Installer mantis ensureFix: 7166.
+ Installer mantis ensureFix: 7291.
+ Installer mantis ensureFix: 6426.
+ !

Item was added:
+ ----- Method: InstallerScripts class>>basicInstall (in category 'as yet unclassified') -----
+ basicInstall
+ 
+ 	| selector |
+ 	
+ 	self options do: [ :ea | 
+ 		selector := ea value asLegalSelector asSymbol.
+ 		(self respondsTo: selector) ifTrue: [ ^ self perform: selector ]
+ 	].
+ 
+ 	^ nil!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldPharo (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldPharo
+ 
+ Installer install:'LevelPlayingField-Monticello15'.
+ !

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak310 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak310
+ 
+ "lets not be beta any more"
+ SystemVersion current version: 'Squeak3.10'.
+ "fix the millisecond clock"
+ Installer mantis ensureFix: 474.
+ Installer mantis ensureFix: 6805.
+ 
+ Installer install:'LevelPlayingField-Monticello15'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptUnloadTraits (in category 'as yet unclassified') -----
+ scriptUnloadTraits
+ 
+ "Phase 1: Disable traits activity and stub out the instance variables that will be removed in Phase 2"
+ 
+ SystemChangeNotifier uniqueInstance
+ noMoreNotificationsFor: ProvidedSelectors current;
+ noMoreNotificationsFor: RequiredSelectors current;
+ noMoreNotificationsFor: LocalSends current.
+ Installer installUrl: 'http://installer.pbwiki.org/f/UnloadTraits-StubOutAcessors.cs'.
+ 
+ "Phase 2: Recompile the image with classes in the old format, ie, without the traitsComposition and localSends instance variables"
+ 
+ [
+ ClassDescription subclass: #Metaclass
+ instanceVariableNames: 'thisClass'
+ classVariableNames: ' '
+ poolDictionaries: ' '
+ category: 'Kernel-Classes'.
+ ClassDescription subclass: #Class
+ instanceVariableNames: 'subclasses name classPool sharedPools environment category'
+ classVariableNames: ' '
+ poolDictionaries: ' '
+ category: 'Kernel-Classes'.
+ ] on: Warning do: [:warning | warning resume].
+ 
+ "Phase 3: Remove all traits and all references to the Traits classes from the image, including methods that refer to traits functionality"
+ 
+ "Kill all traits" "variables are nil-ed out to prevent obsolete refs later"
+ Smalltalk allTraits do: [:trait | trait removeFromSystem. trait := nil].
+ "Recompile all methods that were part of a trait"
+ SystemNavigation default allBehaviorsDo: [:class | class selectorsAndMethodsDo: [:sel :method | class ~~ method methodClass ifTrue: [class recompile: sel]. method := nil]. class := nil].
+ "Remove references to traits from various places in the code"
+ Installer installUrl: 'http://installer.pbwiki.org/f/UnloadTraits-ClearRefs.cs'.
+ 
+ "Phase 4: Unload the Traits package and install the Traits compatability stubs for Monticello"
+ 
+ Installer unload: 'Traits'.
+ Installer installUrl: 'http://installer.pbwiki.org/f/TraitsStubs.cs'.
+ 
+ 
+ !

Item was added:
+ ----- Method: InstallerScripts>>scriptUniverses (in category 'as yet unclassified') -----
+ scriptUniverses
+ 
+ Installer ss project: 'XMLSupport'; install: 'XML-Parser'.
+ Installer ss project: 'universes'; install: 'Universes'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldCroquet (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldCroquet
+ 
+ Installer mantis fixBug: '7087 Enable MC File in for Croquet'.
+ Installer mantis fixBug: '7088 Parser cannot parse the selector of a method with an underscore assignment'.
+ 
+ Installer install:'LevelPlayingField-Monticello15'.
+ Installer ss project: 'mc'; install: 'TweakMC'.!

Item was added:
+ Installer subclass: #InstallerScripts
+ 	instanceVariableNames: 'script isStepping'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!
+ 
+ !InstallerScripts commentStamp: 'kph 2/23/2009 02:27' prior: 0!
+ (self new addPackage: 'Example') options collect: [ :ea  | ea value asLegalSelector asSymbol ]  #(#scriptExampleSqueak310forKPH #scriptExampleSqueak310 #scriptExampleSqueak310)!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldLauncherLaunch (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldLauncherLaunch
+ 
+  Installer mantis fixBug: '6086 Improved Line End Convention Specification'.
+  
+  Installer squeaksource project:'Installer';
+         install:  'Installer-Launcher'.
+  
+  Installer mantis fixBug: '5851 Refactor SmalltalkImage saveAs'.
+  
+  Transcript cr; cr; show:'You now have a level playing field.'.
+  Transcript cr; cr; show:'Launcher now processing additional commandline parameters...'.
+  (Smalltalk at: #Launcher) new
+  		actionSelector: #launchFrom: ;
+  		image: SmalltalkImage current;
+  		commandLineClass: Launcher;
+  		beFirstTime;
+  		begin;
+  		yourself.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingField (in category 'as yet unclassified') -----
+ scriptLevelPlayingField
+ 	Transcript cr; show: 'Your image version is not explicitly supported by LPF yet. Contact maintainers for details'.
+ 	Installer install:'LevelPlayingField-Monticello15'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak3102 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak3102
+ 
+ 	^ self scriptLevelPlayingFieldSqueak3101!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak37 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak37
+ 
+ Installer debug mantis fixBug: '6476 Enable MC File in if before 3.9'.
+ 
+ "add ifNil:ifNotNil"
+ Installer installUrl: 'http://installer.pbwiki.com/f/For37.cs'.
+ 
+ Installer install:'LevelPlayingField-Monticello15'.
+ 
+ Installer squeaksource project: 'Glorp37Compat'; install: 'Glorp3.7Compatibility'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak39 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak39
+ 
+ Installer install:'LevelPlayingField-Monticello15'.
+ !

Item was added:
+ ----- Method: InstallerScripts class>>options (in category 'as yet unclassified') -----
+ options
+ 
+ 	^ { 
+ 	
+ 	['script', self package, Smalltalk version, 'for' ,  Utilities authorInitialsPerSe asUppercase].
+ 	['script', self package, Smalltalk version].
+ 	['script', self package, SystemVersion current majorMinorVersion].
+ 	
+ 	}!

Item was added:
+ ----- Method: InstallerScripts>>basicInstall (in category 'as yet unclassified') -----
+ basicInstall
+ 
+ 	| selector |
+ 	
+ 	self options do: [ :ea | 
+ 		selector := ea value asLegalSelector asSymbol.
+ 		(self respondsTo: selector) ifTrue: [ self perform: selector. ^ true ]
+ 	].
+ 
+ 	^ nil!

Item was added:
+ ----- Method: InstallerScripts>>product (in category 'as yet unclassified') -----
+ product
+ 	| vers |
+ 	vers := Smalltalk version.
+ 	
+ 	1 to: vers size do: [ :n | (vers at: n) isDigit ifTrue: [ ^ Smalltalk version first: n-1 ] ]
+ 	
+ "
+ self new product
+ "!

Item was added:
+ ----- Method: InstallerScripts>>scriptMonticello16Beta (in category 'as yet unclassified') -----
+ scriptMonticello16Beta
+ "
+ Monticello 1.6 will be all about truly atomic loading, thanks to SystemEditor. The atomic loader comes with every copy of Monticello 1.5, but is disabled by default. So this script just loads up MC 1.5, SystemEditor, and enables the atomic loader.
+ 
+ Note that this is beta level software, but I think it mostly works
+ 
+ There is no support for Traits yet, or for Tweak fields, so you won't be able to load Traits or Nile or parts of Omnibrowser with this enabled.
+ To use the stable loader, disable the preference monticello > useMonticelloAtomicLoader
+ "
+ 
+ Installer ss project: 'SystemEditor';
+ install: 'SystemEditor-Core';
+ install: 'SystemEditor-Squeak'.
+ Preferences setPreference: #useMonticelloAtomicLoader toValue: true.!

Item was added:
+ ----- Method: InstallerScripts>>options (in category 'as yet unclassified') -----
+ options
+ 
+ 	^ { 
+ 	
+ 	['script', self package, Smalltalk version, 'for' ,  Utilities authorInitialsPerSe asUppercase].
+ 	['script', self package, Smalltalk version].
+ 	['script', self package, SystemVersion current majorMinorVersion].
+ 	['script', self package, self product ].
+ 	['script', self package ].
+ 	
+ 	}!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldetoys (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldetoys
+ 
+ 	^ self scriptLevelPlayingFieldSqueak38!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldPreamblePharo (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldPreamblePharo
+ 
+ Transcript show: 'All fixes are already in Pharo 10236'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldPostscript (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldPostscript
+ 
+ Installer upgrade.
+ 
+ Smalltalk organization removeSystemCategory: 'Monticello-Tests'.
+ (MCPackage named: 'Monticello') workingCopy unregister.
+ (MCPackage named: 'PackageInfo') workingCopy unregister.
+ (MCPackage named: 'MonticelloConfigurations') workingCopy unregister.
+ 
+ SystemOrganization removeEmptyCategories.
+ 
+ MCMethodDefinition freeSomeSpace.
+ MCFileBasedRepository freeSomeSpace.
+ DataStream initialize.
+ 
+ Transcript show: 'Postscript: Squeakmap Update '.
+ 
+ [ Installer sm update ] ifError: [ Transcript show: '(Squeakmap not installed)'.].
+ 
+ Installer install:'LevelPlayingField-LauncherLaunch'.
+ !

Item was added:
+ ----- Method: InstallerScripts>>scriptLogging (in category 'as yet unclassified') -----
+ scriptLogging
+ 
+  Installer mantis ensureFix: '7219 Improve Streams Usage Readability'.
+  Installer ss project: 'Logging';
+       install: 'ProcessSpecific';
+       install: 'Logging'.!

Item was changed:
  ----- Method: Installer class>>webInstall: (in category 'web') -----
  webInstall: webPageName
  
- 	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
  	^ self web install: webPageName
  !

Item was added:
+ ----- Method: InstallerScripts>>scriptLPFPreamble (in category 'as yet unclassified') -----
+ scriptLPFPreamble!

Item was added:
+ ----- Method: InstallerScripts>>scriptPackages (in category 'as yet unclassified') -----
+ scriptPackages
+ 
+ Installer mantis ensureFix: '7219 Streams Readability'.
+ Installer mantis ensureFix: '7166 Speedup allSelectors add allSelectorsBelow'.
+ Installer mantis ensureFix: '7272 BlockContext equality testing missing'.
+ Installer squeaksource project: 'Sake'; install: 'Sake-Core'.
+ Installer squeaksource project: 'Packages';
+ install: 'Sake-Packages';
+ install: 'Packages-Library'.!

Item was added:
+ ----- Method: InstallerScripts>>scriptLevelPlayingFieldSqueak3101 (in category 'as yet unclassified') -----
+ scriptLevelPlayingFieldSqueak3101
+ 
+ Installer install:'LevelPlayingField-Monticello15'.!

Item was changed:
+ ----- Method: Installer class>>install: (in category 'action report') -----
+ install: scriptName
- ----- Method: Installer class>>install: (in category 'web') -----
- install: webPageName
  
+ 	^ (self scripts install: scriptName) ifNil:[ self web install: scriptName ]
- 	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
- 
- 	^ self web install: webPageName
  !



More information about the Packages mailing list