SystemOrganization addCategory: #'Helvetia-Loader'! Object subclass: #CHHelvetiaLoader instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Helvetia-Loader'! !CHHelvetiaLoader class methodsFor: 'installing-settings (4000)' stamp: 'lr 4/26/2010 20:25'! defineCleanup MCCacheRepository instVarNamed: 'default' put: nil. MCFileBasedRepository flushAllCaches. MCMethodDefinition shutDown. MCDefinition clearInstances. Smalltalk flushClassNameCache. Smalltalk organization removeEmptyCategories. Smalltalk allClassesAndTraitsDo: [ :each | each organization removeEmptyCategories; sortCategories. each class organization removeEmptyCategories; sortCategories ]. Smalltalk garbageCollect. Symbol compactSymbolTable! ! !CHHelvetiaLoader class methodsFor: 'installing-settings (4000)' stamp: 'lr 4/26/2010 20:23'! defineDesign UIThemeWatery2 beCurrent. World submorphs do: [ :each | (each isKindOf: SketchMorph) ifTrue: [ each delete ] ] ! ! !CHHelvetiaLoader class methodsFor: 'installing-settings (4000)' stamp: 'lr 4/26/2010 20:23'! defineFonts StrikeFont installDejaVu. Preferences setDefaultFonts: #( (setBalloonHelpFontTo: 'BitmapDejaVu' 9) (setButtonFontTo: 'BitmapDejaVu' 9) (setCodeFontTo: 'BitmapDejaVu' 9) (setHaloLabelFontTo: 'BitmapDejaVu' 9) (setListFontTo: 'BitmapDejaVu' 9) (setMenuFontTo: 'BitmapDejaVu' 9) (setSystemFontTo: 'BitmapDejaVu' 9) (setWindowTitleFontTo: 'BitmapDejaVuBold' 12)) ! ! !CHHelvetiaLoader class methodsFor: 'installing-settings (4000)' stamp: 'lr 4/26/2010 20:24'! definePreferences Preferences enable: #scrollBarsNarrow. Preferences enable: #menuColorFromWorld. Preferences disable: #scrollBarsWithoutMenuButton. Preferences disable: #useNewDiffToolsForMC. Preferences disable: #duplicateAllControlAndAltKeys. Preferences disable: #fadedBackgroundWindows. Preferences disable: #windowAnimation. Preferences disable: #noWindowAnimationForClosing! ! !CHHelvetiaLoader class methodsFor: 'initialization' stamp: 'lr 1/11/2010 10:53'! initialize self specification do: [ :pragma | pragma arguments first isString ifTrue: [ ProgressNotification signal: '' extra: pragma arguments first ]. self perform: pragma selector ] displayingProgress: 'Loading Helvetia'! ! !CHHelvetiaLoader class methodsFor: 'installing-tools (2000)' stamp: 'lr 2/14/2010 11:01'! loadDevelopmentTools Gofer new renggli: 'unsorted'; package: 'Shout'; package: 'RoelTyper'; package: 'ECompletion'; package: 'ECompletionOmniBrowser'; load! ! !CHHelvetiaLoader class methodsFor: 'installing-helvetia (3000)' stamp: 'lr 4/27/2010 16:37'! loadHelvetia Gofer new renggli: 'helvetia'; package: 'AST-Compiler'; package: 'AST-Semantic'; package: 'QuasiQuote'; package: 'Helvetia-Core'; load. CHCompiler enable! ! !CHHelvetiaLoader class methodsFor: 'installing-helvetia (3000)' stamp: 'lr 2/19/2010 11:57'! loadHelvetiaExamples "Since some smart-ass tried to make Monticello atomic (and failed miserabely), we do the load operation manually. This compiled and loads all the code nicely in order, nothing 'smart' here." | gofer | gofer := Gofer new. gofer renggli: 'helvetia'; package: 'Cutie-Helvetia'. gofer resolved do: [ :reference | | definitions errors | definitions := reference version snapshot definitions asSortedCollection asOrderedCollection. [ [ definitions isEmpty ] whileFalse: [ errors := OrderedCollection new. definitions do: [ :definition | [ definition load ] on: Error do: [ :err | errors addLast: definition ] ]. definitions size = errors size ifTrue: [ ^ errors explore ]. definitions := errors ] ] on: InMidstOfFileinNotification do: [ :err | err resume: true ] ]. gofer load! ! !CHHelvetiaLoader class methodsFor: 'installing-tools (2000)' stamp: 'lr 2/14/2010 10:59'! loadOmniBrowser Gofer new renggli: 'omnibrowser'; package: 'OmniBrowser'; package: 'OB-Standard'; package: 'OB-Morphic'; package: 'OB-Shout'; package: 'OB-Refactory'; package: 'OB-Regex'; package: 'OB-SUnitIntegration'; load. SystemBrowser default: (Smalltalk at: #OBSystemBrowserAdaptor)! ! !CHHelvetiaLoader class methodsFor: 'installing-tools (2000)' stamp: 'lr 2/14/2010 11:01'! loadPetitParser Gofer new renggli: 'petit'; package: 'PetitParser'; package: 'PetitAnalyzer'; package: 'PetitSmalltalk'; load! ! !CHHelvetiaLoader class methodsFor: 'installing-tools (2000)' stamp: 'lr 2/18/2010 20:38'! loadRefactoringEngine Gofer new squeaksource: 'rb'; package: 'AST-Core'; package: 'AST-Tests-Core'; package: 'Refactoring-Core'; package: 'Refactoring-Tests-Core'; package: 'Refactoring-Spelling'; load! ! !CHHelvetiaLoader class methodsFor: 'installing-validation (1000)' stamp: 'lr 4/26/2010 22:16'! patchMonticello MCPackageLoader compile: 'basicLoad errorDefinitions := OrderedCollection new. [[additions do: [:ea | self tryToLoad: ea] displayingProgress: ''Loading...''. removals do: [:ea | ea unload] displayingProgress: ''Cleaning up...''. self shouldWarnAboutErrors ifTrue: [self warnAboutErrors]. errorDefinitions do: [:ea | ea loadOver: (self obsoletionFor: ea)] displayingProgress: ''Reloading...''. additions do: [:ea | ea postloadOver: (self obsoletionFor: ea)] displayingProgress: ''Initializing...''] on: InMidstOfFileinNotification do: [:n | n resume: true]] ensure: [self flushChangesFile]' classified: #private withStamp: 'lr 4/26/2010 20:13' notifying: SyntaxError new. MCPackageLoader compile: 'tryToLoad: aDefinition [aDefinition loadOver: (self obsoletionFor: aDefinition)] on: Error do: [errorDefinitions add: aDefinition]' classified: #private withStamp: 'lr 4/26/2010 20:13' notifying: SyntaxError new. MCWorkingCopy allManagers do: [ :each | each packageName = 'Monticello' ifTrue: [ each modified: false ] ]! ! !CHHelvetiaLoader class methodsFor: 'initialization' stamp: 'lr 1/11/2010 10:46'! specification ^ Pragma allNamed: #install:priority: in: self class sortedByArgument: 2! ! !CHHelvetiaLoader class methodsFor: 'installing-validation (1000)' stamp: 'lr 4/26/2010 20:19'! validatePlatform (SystemVersion current version beginsWith: 'PharoCore1.0') ifFalse: [ self notify: 'Helvetia might not work with this image: ' , SystemVersion current version , '. Please consider using a PharoCore 1.0 image.' ]. (SystemVersion current highestUpdate >= 10517) ifFalse: [ self notify: 'Helvetia might not work with this image: ' , SystemVersion current version , '. Please consider using a PharoCore 1.0 image.' ]! ! CHHelvetiaLoader initialize!