[squeak-dev] The Trunk: Tools-fbs.485.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jul 17 13:19:53 UTC 2013


Frank Shearar uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-fbs.485.mcz

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

Name: Tools-fbs.485
Author: fbs
Time: 11 July 2013, 8:29:37.689 pm
UUID: 042ee2b0-9ecd-cc46-b83a-fba8972f38fe
Ancestors: Tools-fbs.484

Undo the FileList2 deprecation. It's premature. Lots of code uses it, and maybe there's a possibility to just rewrite its UI using ToolBuilder...?

We don't need to revert the corresponding 45Deprecated-fbs.8 because I pulled that from the update stream.

=============== Diff against Tools-fbs.484 ===============

Item was added:
+ FileList subclass: #FileList2
+ 	instanceVariableNames: 'showDirsInFileList currentDirectorySelected fileSelectionBlock dirSelectionBlock optionalButtonSpecs modalView directoryChangeBlock ok'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tools-FileList'!
+ FileList2 class
+ 	instanceVariableNames: 'lastSelDir'!
+ 
+ !FileList2 commentStamp: 'BJP 11/19/2003 21:13' prior: 0!
+ Some variations on FileList that
+ - use a hierarchical pane to show folder structure
+ - use different pane combinations, button layouts and prefiltering for specific uses
+ 
+ FileList2 morphicView openInWorld				"an alternative to the standard FileList"
+ FileList2 morphicViewNoFile openInWorld			"useful for selecting, but not viewing"
+ FileList2 morphicViewProjectLoader openInWorld	"useful for finding and loading projects"
+ FileList2 modalFolderSelector						"allows the user to select a folder"
+ 
+ 
+ 
+ !
+ FileList2 class
+ 	instanceVariableNames: 'lastSelDir'!

Item was added:
+ ----- Method: FileList2 class>>addFullPanesTo:from: (in category 'utility') -----
+ addFullPanesTo: window from: aCollection
+ 
+ 	
+ 
+ 	aCollection do: [ :each | | frame |
+ 		frame := LayoutFrame 
+ 			fractions: each second 
+ 			offsets: each third.
+ 		window addMorph: each first fullFrame: frame.
+ 	]!

Item was added:
+ ----- Method: FileList2 class>>blueButtonText:textColor:color:inWindow: (in category 'blue ui') -----
+ blueButtonText: aString textColor: textColor color: aColor inWindow: window 
+ 	| result |
+ 	result := window
+ 				fancyText: aString translated
+ 				font: Preferences standardEToysFont
+ 				color: textColor.
+ 	result setProperty: #buttonText toValue: aString;
+ 		 hResizing: #rigid;
+ 		 extent: 100 @ 20;
+ 		 layoutInset: 4;
+ 		 borderWidth: ColorTheme current dialogButtonBorderWidth;
+ 		 useRoundedCorners.
+ 	aColor isNil
+ 		ifFalse: [""result color: aColor. result borderColor: aColor muchDarker].
+ 	^ result!

Item was added:
+ ----- Method: FileList2 class>>blueButtonText:textColor:color:inWindow:balloonText:selector:recipient: (in category 'blue ui') -----
+ blueButtonText: aString textColor: textColor color: aColor inWindow: window balloonText: balloonText selector: sel recipient: recip 
+ 	| result |
+ 	result := window
+ 				fancyText: aString translated
+ font: Preferences standardEToysFont
+ 				color: textColor.
+ 	result setProperty: #buttonText toValue: aString;
+ 		 hResizing: #rigid;
+ 		 extent: 100 @ 20;
+ 		 layoutInset: 4;
+ 		 borderWidth: ColorTheme current dialogButtonBorderWidth;
+ 		 useRoundedCorners;
+ 		 setBalloonText: balloonText.
+ 	result
+ 		on: #mouseUp
+ 		send: sel
+ 		to: recip.
+ 	aColor isNil
+ 		ifFalse: [""
+ 			result color: aColor.
+ 			result borderColor: aColor muchDarker].
+ 	^ result!

Item was added:
+ ----- Method: FileList2 class>>blueButtonText:textColor:inWindow: (in category 'blue ui') -----
+ blueButtonText: aString textColor: textColor inWindow: window 
+ 	^ self
+ 		blueButtonText: aString
+ 		textColor: textColor
+ 		color: nil
+ 		inWindow: window!

Item was added:
+ ----- Method: FileList2 class>>blueButtonText:textColor:inWindow:balloonText:selector:recipient: (in category 'blue ui') -----
+ blueButtonText: aString textColor: textColor inWindow: window balloonText: balloonText selector: sel recipient: recip 
+ 	^ self
+ 		blueButtonText: aString
+ 		textColor: textColor
+ 		color: nil
+ 		inWindow: window
+ 		balloonText: balloonText
+ 		selector: sel
+ 		recipient: recip !

Item was added:
+ ----- Method: FileList2 class>>enableTypeButtons:info:forDir: (in category 'blue ui') -----
+ enableTypeButtons: typeButtons info: fileTypeInfo forDir: aDirectory
+ 
+ 	| foundSuffixes firstEnabled |
+ 
+ 	firstEnabled := nil.
+ 	foundSuffixes := (aDirectory ifNil: [ #()] ifNotNil: [ aDirectory fileNames]) collect: [ :each | (each findTokens: '.') last asLowercase].
+ 	foundSuffixes := foundSuffixes asSet.
+ 	fileTypeInfo with: typeButtons do: [ :info :button | | enableIt fileSuffixes |
+ 		fileSuffixes := info second.
+ 		enableIt := fileSuffixes anySatisfy: [ :patt | foundSuffixes includes: patt].
+ 		button 
+ 			setProperty: #enabled 
+ 			toValue: enableIt.
+ 		enableIt ifTrue: [firstEnabled ifNil: [firstEnabled := button]].
+ 	].
+ 	firstEnabled ifNotNil: [^firstEnabled mouseUp: nil].
+ 	typeButtons do: [ :each | each color: Color gray].
+ 
+ !

Item was added:
+ ----- Method: FileList2 class>>endingSpecs (in category 'blue ui') -----
+ endingSpecs
+ 	"Answer a collection of specs to build the selective 'find anything' tool called by the Navigator. This version uses the services registry to do so."
+ 	"FileList2 morphicViewGeneralLoaderInWorld: World"
+ 	| categories specs rejects |
+ 	rejects := #(addFileToNewZip: compressFile: openInZipViewer: extractAllFrom: openOn:).
+ 	categories := #(
+ 		('Art' ('bmp' 'gif' 'jpg' 'jpeg' 'form' 'png' 'pcx' 'xbm' 'xpm' 'ppm' 'pbm'))
+ 		('Morphs' ('morph' 'morphs' 'sp'))
+ 		('Projects' ('extseg' 'project' 'pr'))
+ 		('MIDI' ('mid' 'midi'))
+ 		('Music' ('mp3'))
+ 		('Movies' ('movie' 'mpg' 'mpeg' 'qt' 'mov'))
+ 		('Flash' ('swf'))
+ 	).
+ 
+ 		"('Books' ('bo'))"
+ 		"('Code' ('st' 'cs'))"
+ 		"('TrueType' ('ttf'))"
+ 		"('3ds' ('3ds'))"
+ 		"('Tape' ('tape'))"
+ 		"('Wonderland' ('wrl'))"
+ 		"('HTML' ('htm' 'html'))"
+ 
+ 	categories first at: 2 put: ImageReadWriter allTypicalFileExtensions.
+ 	specs := OrderedCollection new.
+ 	categories do: [ :cat | | catSpecs catServices okExtensions services |
+ 		services := Dictionary new.
+ 		catSpecs := Array new: 3.
+ 		catServices := OrderedCollection new.
+ 		okExtensions := Set new.
+ 
+ 		cat second do: [ :ext | (FileList itemsForFile: 'fred.',ext) do: [ :i |
+ 			(rejects includes: i selector) ifFalse: [
+ 				okExtensions add: ext.
+ 				services at: i label put: i ]]].
+ 		services do: [ :svc | catServices add: svc ].
+ 		services isEmpty ifFalse: [ 
+ 			catSpecs at: 1 put: cat first;
+ 				at: 2 put: okExtensions;
+ 				at: 3 put: catServices.
+ 			specs add: catSpecs ]
+ 	].
+ 	^specs
+ !

Item was added:
+ ----- Method: FileList2 class>>hideSqueakletDirectoryBlock (in category 'as yet unclassified') -----
+ hideSqueakletDirectoryBlock
+ 	^[:dirName| (dirName sameAs: 'Squeaklets') not]!

Item was added:
+ ----- Method: FileList2 class>>lastSelDir (in category 'accessing') -----
+ lastSelDir
+ 	"Return the last selected directory or the default directory if no directory was selected so far."
+ 
+ 	^lastSelDir ifNil: [ lastSelDir := FileDirectory default ]!

Item was added:
+ ----- Method: FileList2 class>>lastSelDir: (in category 'accessing') -----
+ lastSelDir: aFileDirectory
+ 	"Store the last selected directory. This will be selected as default in newly opened file or folder selectors"
+ 	
+ 	^lastSelDir := aFileDirectory!

Item was added:
+ ----- Method: FileList2 class>>modalFileSelector (in category 'modal dialogs') -----
+ modalFileSelector
+ 
+ 	| window |
+ 
+ 	window := self morphicViewFileSelector.
+ 	window openCenteredInWorld.
+ 	self modalLoopOn: window.
+ 	^(window valueOfProperty: #fileListModel) getSelectedFile!

Item was added:
+ ----- Method: FileList2 class>>modalFileSelectorForSuffixes: (in category 'modal dialogs') -----
+ modalFileSelectorForSuffixes: aList
+ 
+ 	| window aFileList |
+ 
+ 	window := self morphicViewFileSelectorForSuffixes: aList.
+ 	aFileList := window valueOfProperty: #fileListModel.
+ 	window openCenteredInWorld.
+ 	self modalLoopOn: window.
+ 	^aFileList getSelectedFile!

Item was added:
+ ----- Method: FileList2 class>>modalFileSelectorForSuffixes:directory: (in category 'modal dialogs') -----
+ modalFileSelectorForSuffixes: aList directory: aDirectory
+ 
+ 	| window aFileList |
+ 
+ 	window := self morphicViewFileSelectorForSuffixes: aList directory: aDirectory.
+ 	aFileList := window valueOfProperty: #fileListModel.
+ 	window openCenteredInWorld.
+ 	self modalLoopOn: window.
+ 	^aFileList getSelectedFile!

Item was added:
+ ----- Method: FileList2 class>>modalFolderSelector (in category 'modal dialogs') -----
+ modalFolderSelector
+ 
+ 	^self modalFolderSelector: self lastSelDir
+ 	!

Item was added:
+ ----- Method: FileList2 class>>modalFolderSelector: (in category 'modal dialogs') -----
+ modalFolderSelector: aDir
+ 
+ 	| window fileModel |
+ 	window := self morphicViewFolderSelector: aDir.
+ 	fileModel := window model.
+ 	window openInWorld: self currentWorld extent: 300 at 400.
+ 	self modalLoopOn: window.
+ 	^fileModel getSelectedDirectory withoutListWrapper!

Item was added:
+ ----- Method: FileList2 class>>modalFolderSelectorForProject: (in category 'modal dialogs') -----
+ modalFolderSelectorForProject: aProject
+ "
+ FileList2 modalFolderSelectorForProject: Project current
+ "
+ 	| window fileModel w |
+ 
+ 	window := FileList2 morphicViewProjectSaverFor: aProject.
+ 	fileModel := window valueOfProperty: #FileList.
+ 	w := self currentWorld.
+ 	window position: w topLeft + (w extent - window extent // 2).
+ 	w addMorphInLayer: window.
+ 	w startSteppingSubmorphsOf: window.
+ 	self modalLoopOn: window.
+ 	^fileModel getSelectedDirectory withoutListWrapper!

Item was added:
+ ----- Method: FileList2 class>>modalFolderSelectorForProjectLoad (in category 'modal dialogs') -----
+ modalFolderSelectorForProjectLoad
+ 
+ 	| window fileModel w |
+ 
+ 	window := self morphicViewProjectLoader2InWorld: self currentWorld reallyLoad: false.
+ 	fileModel := window valueOfProperty: #FileList.
+ 	w := self currentWorld.
+ 	window position: w topLeft + (w extent - window extent // 2).
+ 	window openInWorld: w.
+ 	self modalLoopOn: window.
+ 	^fileModel getSelectedDirectory withoutListWrapper!

Item was added:
+ ----- Method: FileList2 class>>modalLoopOn: (in category 'utility') -----
+ modalLoopOn: aMorph
+ 	[aMorph world notNil] whileTrue: [
+ 		aMorph outermostWorldMorph doOneCycle.
+ 	].!

Item was added:
+ ----- Method: FileList2 class>>morphicViewFileSelector (in category 'morphic ui') -----
+ morphicViewFileSelector
+ 
+ 	^self morphicViewFileSelectorForSuffixes: nil
+ !

Item was added:
+ ----- Method: FileList2 class>>morphicViewFileSelectorForSuffixes: (in category 'morphic ui') -----
+ morphicViewFileSelectorForSuffixes: aList 
+ 	"Answer a morphic file-selector tool for the given suffix list."
+ 	
+ 	^self morphicViewFileSelectorForSuffixes: aList directory: self lastSelDir!

Item was added:
+ ----- Method: FileList2 class>>morphicViewFileSelectorForSuffixes:directory: (in category 'morphic ui') -----
+ morphicViewFileSelectorForSuffixes: aList directory: dir
+ 	"Answer a morphic file-selector tool for the given suffix list and the given directory."
+ 
+ 	| aFileList window fixedSize midLine gap |
+ 	aFileList := self new directory: dir.
+ 	aFileList optionalButtonSpecs: aFileList okayAndCancelServices.
+ 	aList ifNotNil:
+ 		[aFileList fileSelectionBlock: [:entry :myPattern |
+ 			entry isDirectory
+ 				ifTrue:
+ 					[false]
+ 				ifFalse:
+ 					[aList includes: (FileDirectory extensionFor: entry name asLowercase)]]].
+ 	window := BorderedMorph new
+ 		layoutPolicy: ProportionalLayout new;
+ 		color: Color lightBlue;
+ 		borderColor: Color blue;
+ 		borderWidth: 4;
+ 		layoutInset: 4;
+ 		extent: 600 at 400;
+ 		useRoundedCorners.
+ 	window setProperty: #fileListModel toValue: aFileList.
+ 	aFileList modalView: window.
+ 	midLine := 0.4.
+ 	fixedSize := 25.
+ 	gap := 5.
+ 	self addFullPanesTo: window from: {
+ 		{self textRow: 'Please select a file'. 0 @ 0 corner: 1 @ 0. 0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0 at fixedSize corner: 0@(fixedSize * 2)}.
+ 		{aFileList morphicDirectoryTreePane. 0 at 0 corner: midLine at 1. 
+ 					gap @(fixedSize * 2) corner: gap negated at 0}.
+ 		{aFileList morphicFileListPane. midLine @ 0 corner: 1 at 1. 
+ 					gap@(fixedSize * 2) corner: gap negated at 0}.
+ 	}.
+ 
+ 	aFileList postOpen.
+ 
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>morphicViewFolderSelector (in category 'morphic ui') -----
+ morphicViewFolderSelector
+ 
+ 	^self morphicViewFolderSelector: FileDirectory default!

Item was added:
+ ----- Method: FileList2 class>>morphicViewFolderSelector: (in category 'morphic ui') -----
+ morphicViewFolderSelector: aDir
+ 	"Answer a tool that allows the user to select a folder"
+ 
+ 	| aFileList window fixedSize |
+ 	aFileList := self new directory: aDir.
+ 	aFileList optionalButtonSpecs: aFileList servicesForFolderSelector.
+ 	window := (SystemWindow labelled: aDir pathName) model: aFileList.
+ 	aFileList modalView: window.
+ 
+ 	fixedSize := 25.
+ 	self addFullPanesTo: window from: {
+ 		{self textRow: 'Please select a folder'. 0 @ 0 corner: 1 @ 0. 
+ 				0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 
+ 				0 at fixedSize corner: 0@(fixedSize * 2)}.
+ 		{aFileList morphicDirectoryTreePane. 0 at 0 corner: 1 at 1.
+ 				0@(fixedSize * 2) corner: 0 at 0}.
+ 	}.
+ 	aFileList postOpen.
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>morphicViewGeneralLoaderInWorld: (in category 'blue ui') -----
+ morphicViewGeneralLoaderInWorld: aWorld
+ "
+ FileList2 morphicViewGeneralLoaderInWorld: self currentWorld
+ "
+ 	| window aFileList buttons treePane textColor1 fileListPane pane2a pane2b fileTypeInfo fileTypeButtons fileTypeRow actionRow |
+ 
+ 	fileTypeInfo := self endingSpecs.
+ 	window := AlignmentMorphBob1 newColumn.
+ 	window hResizing: #shrinkWrap; vResizing: #shrinkWrap.
+ 	textColor1 := Color r: 0.742 g: 0.839 b: 1.0.
+ 	aFileList := self new directory: FileDirectory default.
+ 	aFileList 
+ 		fileSelectionBlock: self projectOnlySelectionBlock;
+ 		modalView: window.
+ 	window
+ 		setProperty: #FileList toValue: aFileList;
+ 		wrapCentering: #center; cellPositioning: #topCenter;
+ 		borderWidth: ColorTheme current dialogBorderWidth;
+ 		borderColor: ColorTheme current dialogBorderColor;
+ 		useRoundedCorners.
+ 
+ 	fileTypeButtons := fileTypeInfo collect: [ :each |
+ 		(self blueButtonText: each first textColor: Color gray inWindow: window)
+ 			setProperty: #enabled toValue: true;
+ 			hResizing: #shrinkWrap;
+ 			useSquareCorners
+ 	].
+ 	buttons := {{'OK'. ColorTheme current okColor}. {'Cancel'. ColorTheme current cancelColor}} collect: [ :each |
+ 		self blueButtonText: each first textColor: textColor1 color: each second inWindow: window
+ 	].
+ 
+ 	treePane := aFileList morphicDirectoryTreePane 
+ 		extent: 250 at 300; 
+ 		retractable: false;
+ 		borderWidth: 0.
+ 	fileListPane := aFileList morphicFileListPane 
+ 		extent: 350 at 300; 
+ 		retractable: false;
+ 		borderWidth: 0.
+ 	window addARow: {window fancyText: 'Find...' translated font: Preferences standardEToysTitleFont color: textColor1}.
+ 	fileTypeRow := window addARowCentered: fileTypeButtons cellInset: 2.
+ 	actionRow := window addARowCentered: {
+ 		buttons first. 
+ 		(Morph new extent: 30 at 5) color: Color transparent. 
+ 		buttons second
+ 	} cellInset: 2.
+ 	window
+ 		addARow: {
+ 				(window inAColumn: {(pane2a := window inARow: {window inAColumn: {treePane}}) 
+ 					useRoundedCorners;
+ 					layoutInset: 0;
+ 					borderWidth: ColorTheme current dialogPaneBorderWidth;
+ 					borderColor: ColorTheme current dialogPaneBorderColor
+ 				}) layoutInset: 10.
+ 				(window inAColumn: {(pane2b := window inARow: {window inAColumn: {fileListPane}}) 
+ 					useRoundedCorners;
+ 					layoutInset: 0;
+ 					borderWidth: ColorTheme current dialogPaneBorderWidth;
+ 					borderColor: ColorTheme current dialogPaneBorderColor
+ 				}) layoutInset: 10.
+ 		}.
+ 	window fullBounds.
+ 	window fillWithRamp: ColorTheme current dialogRampOrColor oriented: 0.65.
+ 	pane2a fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35).
+ 	pane2b fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35).
+ "
+ 	buttons do: [ :each |
+ 		each fillWithRamp: ColorTheme current dialogButtonsRampOrColor oriented: (0.75 @ 0).
+ 	].
+ "
+ 	fileTypeButtons do: [ :each | 
+ 		each 
+ 			on: #mouseUp 
+ 			send: #value:value: 
+ 			to: [ :evt :morph | 
+ 				self update: actionRow in: window fileTypeRow: fileTypeRow morphUp: morph.
+ 			]
+ 	].
+ 	buttons first on: #mouseUp send: #okHit to: aFileList.
+ 	buttons second on: #mouseUp send: #cancelHit to: aFileList.
+ 	aFileList postOpen.
+ 	window position: aWorld topLeft + (aWorld extent - window extent // 2).
+ 	aFileList directoryChangeBlock: [ :newDir |
+ 		self update: actionRow in: window fileTypeRow: fileTypeRow morphUp: nil.
+ 		self enableTypeButtons: fileTypeButtons info: fileTypeInfo forDir: newDir.
+ 	].
+ 	aFileList directory: aFileList directory.
+ 	window adoptPaneColor: (Color r: 0.548 g: 0.677 b: 1.0).
+ 	window becomeModal.
+ 	^ window openInWorld: aWorld.!

Item was added:
+ ----- Method: FileList2 class>>morphicViewImageViewer (in category 'morphic ui') -----
+ morphicViewImageViewer
+ 
+ 	| dir aFileList window midLine fixedSize |
+ 
+ 	dir := FileDirectory default.
+ 	aFileList := self new directory: dir.
+ 	aFileList optionalButtonSpecs: aFileList specsForImageViewer.
+ 	aFileList fileSelectionBlock: [ :entry :myPattern |
+ 		entry isDirectory ifTrue: [
+ 			false
+ 		] ifFalse: [
+ 			#('bmp' 'gif' 'jpg' 'form' 'png') includes: 
+ 					 (FileDirectory extensionFor: entry name asLowercase)
+ 		]
+ 	].
+ 	window := (SystemWindow labelled: dir pathName) model: aFileList.
+ 
+ 	fixedSize := 25.
+ 	midLine := 0.4.
+ 	self addFullPanesTo: window from: {
+ 		{aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0.
+ 				0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList morphicDirectoryTreePane. 0 at 0 corner: midLine at 1.
+ 				0 at fixedSize corner: 0 at 0}.
+ 		{aFileList morphicFileListPane. midLine @ 0 corner: 1 at 1.
+ 				0 at fixedSize corner: 0 at 0}.
+ 	}.
+ 	aFileList postOpen.
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>morphicViewNoFile (in category 'morphic ui') -----
+ morphicViewNoFile
+ 
+ 	| dir aFileList window midLine fixedSize |
+ 
+ 	dir := FileDirectory default.
+ 	aFileList := self new directory: dir.
+ 	window := (SystemWindow labelled: dir pathName) model: aFileList.
+ 
+ 	fixedSize := 25.
+ 	midLine := 0.4.
+ 	self addFullPanesTo: window from: {
+ 		{aFileList morphicPatternPane. 0 at 0 corner: 0.3 at 0. 0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList optionalButtonRow. 0.3 @ 0 corner: 1 at 0. 0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList morphicDirectoryTreePane. 0 at 0 corner: midLine at 1. 0 at fixedSize corner: 0 at 0}.
+ 		{aFileList morphicFileListPane. midLine @ 0 corner: 1 at 1. 0 at fixedSize corner: 0 at 0}.
+ 	}.
+ 	aFileList postOpen.
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>morphicViewProjectLoader (in category 'morphic ui') -----
+ morphicViewProjectLoader
+ 
+ 	| dir aFileList window midLine fixedSize |
+ 
+ 	dir := FileDirectory default.
+ 	aFileList := self new directory: dir.
+ 	aFileList optionalButtonSpecs: aFileList servicesForProjectLoader.
+ 	aFileList fileSelectionBlock: self projectOnlySelectionBlock.
+ 	window := (SystemWindow labelled: dir pathName) model: aFileList.
+ 
+ 	fixedSize := 25.
+ 	midLine := 0.4.
+ 	self addFullPanesTo: window from: {
+ 		{aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0 at 0 corner: 0 at fixedSize}.
+ 		{aFileList morphicDirectoryTreePane. 0 at 0 corner: midLine at 1. 0 at fixedSize corner: 0 at 0}.
+ 		{aFileList morphicFileListPane. midLine @ 0 corner: 1 at 1. 0 at fixedSize corner: 0 at 0}.
+ 	}.
+ 	aFileList postOpen.
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>morphicViewProjectLoader2InWorld: (in category 'blue ui') -----
+ morphicViewProjectLoader2InWorld: aWorld
+ 
+ 	^self morphicViewProjectLoader2InWorld: aWorld reallyLoad: true!

Item was added:
+ ----- Method: FileList2 class>>morphicViewProjectLoader2InWorld:reallyLoad: (in category 'blue ui') -----
+ morphicViewProjectLoader2InWorld: aWorld reallyLoad: aBoolean
+ 
+ 	^self 
+ 		morphicViewProjectLoader2InWorld: aWorld 
+ 		reallyLoad: aBoolean
+ 		dirFilterType: #initialDirectoryList
+ !

Item was added:
+ ----- Method: FileList2 class>>morphicViewProjectLoader2InWorld:reallyLoad:dirFilterType: (in category 'blue ui') -----
+ morphicViewProjectLoader2InWorld: aWorld reallyLoad: aBoolean dirFilterType: aSymbol
+ 
+ 	| window aFileList buttons treePane textColor1 fileListPane pane2a pane2b treeExtent filesExtent |
+ 
+ 	window := AlignmentMorphBob1 newColumn.
+ 	window hResizing: #shrinkWrap; vResizing: #shrinkWrap.
+ 	textColor1 := Color r: 0.742 g: 0.839 b: 1.0.
+ 	aFileList := self new directory: FileDirectory default.
+ 	aFileList 
+ 		optionalButtonSpecs: aFileList servicesForProjectLoader;
+ 		fileSelectionBlock: (
+ 			aSymbol == #limitedSuperSwikiDirectoryList ifTrue: [
+ 				MessageSend receiver: self selector: #projectOnlySelectionMethod:
+ 			] ifFalse: [
+ 				self projectOnlySelectionBlock
+ 			]
+ 		);
+ 		"dirSelectionBlock: self hideSqueakletDirectoryBlock;"
+ 		modalView: window.
+ 	window
+ 		setProperty: #FileList toValue: aFileList;
+ 		wrapCentering: #center; cellPositioning: #topCenter;
+ 		borderWidth: ColorTheme current dialogBorderWidth;
+ 		borderColor: ColorTheme current dialogBorderColor;
+ 		useRoundedCorners.
+ 	buttons := {{'OK'. ColorTheme current okColor}. {'Cancel'. ColorTheme current cancelColor}} collect: [ :each |
+ 		self blueButtonText: each first textColor: textColor1 color: each second inWindow: window
+ 	].
+ 
+ 	aWorld width < 800 ifTrue: [
+ 		treeExtent := 150 at 300.
+ 		filesExtent := 350 at 300.
+ 	] ifFalse: [
+ 		treeExtent := 250 at 300.
+ 		filesExtent := 350 at 300.
+ 	].
+ 	(treePane := aFileList morphicDirectoryTreePaneFiltered: aSymbol)
+ 		extent: treeExtent; 
+ 		retractable: false;
+ 		borderWidth: 0.
+ 	fileListPane := aFileList morphicFileListPane 
+ 		extent: filesExtent; 
+ 		retractable: false;
+ 		borderWidth: 0.
+ 	window
+ 		addARow: {
+ 			window fancyText: 'Load A Project' translated font: Preferences standardEToysTitleFont color: textColor1
+ 		};
+ 		addARowCentered: {
+ 			buttons first. 
+ 			(Morph new extent: 30 at 5) color: Color transparent. 
+ 			buttons second
+ 		};
+ 		addARow: {
+ 			window fancyText: 'Please select a project' translated  font: Preferences standardEToysFont color: textColor1
+ 		};
+ 		addARow: {
+ 				(window inAColumn: {(pane2a := window inARow: {window inAColumn: {treePane}}) 
+ 					useRoundedCorners;
+ 					layoutInset: 0;
+ 					borderWidth: ColorTheme current dialogPaneBorderWidth;
+ 					borderColor: ColorTheme current dialogPaneBorderColor
+ 				}) layoutInset: 10.
+ 				(window inAColumn: {(pane2b := window inARow: {window inAColumn: {fileListPane}}) 
+ 					useRoundedCorners;
+ 					layoutInset: 0;
+ 					borderWidth: ColorTheme current dialogPaneBorderWidth;
+ 					borderColor: ColorTheme current dialogPaneBorderColor
+ 				}) layoutInset: 10.
+ 		}.
+ 	window fullBounds.
+ 	window fillWithRamp: ColorTheme current dialogRampOrColor oriented: 0.65.
+ 	pane2a fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35).
+ 	pane2b fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35).
+ "
+ 	buttons do: [ :each |
+ 		each fillWithRamp: ColorTheme current dialogButtonsRampOrColor oriented: (0.75 @ 0).
+ 	].
+ "
+ 	buttons first 
+ 		on: #mouseUp 
+ 		send: (aBoolean ifTrue: [#okHitForProjectLoader] ifFalse: [#okHit])
+ 		to: aFileList.
+ 	buttons second on: #mouseUp send: #cancelHit to: aFileList.
+ 	aFileList postOpen.
+ 	window position: aWorld topLeft + (aWorld extent - window extent // 2).
+ 	window adoptPaneColor: (Color r: 0.548 g: 0.677 b: 1.0).
+ 	window becomeModal.
+ 	^ window openInWorld: aWorld.!

Item was added:
+ ----- Method: FileList2 class>>morphicViewProjectSaverFor: (in category 'blue ui') -----
+ morphicViewProjectSaverFor: aProject
+ "
+ (FileList2 morphicViewProjectSaverFor: Project current) openInWorld
+ "
+ 	| window aFileList buttons treePane pane2 textColor1 option treeExtent buttonData buttonRow |
+ 
+ 	textColor1 := Color r: 0.742 g: 0.839 b: 1.0.
+ 	aFileList := self new directory: ServerDirectory projectDefaultDirectory.
+ 	aFileList dirSelectionBlock: self hideSqueakletDirectoryBlock.
+ 	window := AlignmentMorphBob1 newColumn.
+ 	window hResizing: #shrinkWrap; vResizing: #shrinkWrap.
+ 	aFileList modalView: window.
+ 	window
+ 		setProperty: #FileList toValue: aFileList;
+ 		wrapCentering: #center; cellPositioning: #topCenter;
+ 		borderWidth: ColorTheme current dialogBorderWidth;
+ 		borderColor: ColorTheme current dialogBorderColor;
+ 		useRoundedCorners.
+ 
+ 	buttonData := Preferences enableLocalSave
+ 				ifTrue: [{
+ 							{'Save'. #okHit. 'Save in the place specified below, and in the Squeaklets folder on your local disk'. ColorTheme current okColor}.
+ 							{'Save on local disk only'. #saveLocalOnlyHit. 'saves in the Squeaklets folder'. ColorTheme current okColor}.
+ 							{'Cancel'. #cancelHit. 'return without saving'. ColorTheme current cancelColor}
+ 						}]
+ 				ifFalse: [{
+ 							{'Save'. #okHit. 'Save in the place specified below, and in the Squeaklets folder on your local disk'. ColorTheme current okColor}.
+ 							{'Cancel'. #cancelHit. 'return without saving'. ColorTheme current cancelColor}
+ 						}].
+ 	buttons := buttonData collect: [ :each |
+ 		(self blueButtonText: each first textColor: textColor1 color: each fourth inWindow: window)
+ 			setBalloonText: each third translated;
+ 			hResizing: #shrinkWrap;
+ 			on: #mouseUp send: each second to: aFileList
+ 	].
+ 
+ 	option := aProject world 
+ 		valueOfProperty: #SuperSwikiPublishOptions 
+ 		ifAbsent: [#initialDirectoryList].
+ 	aProject world removeProperty: #SuperSwikiPublishOptions.
+ 
+ 	treeExtent := World height < 500
+ 						ifTrue: [ 350 at 150 ]
+ 						ifFalse: [ 350 at 300 ].
+ 
+ 	(treePane := aFileList morphicDirectoryTreePaneFiltered: option) 
+ 		extent: treeExtent; 
+ 		retractable: false;
+ 		borderWidth: 0.
+ 	window
+ 		addARowCentered: {
+ 			window fancyText: 'Publish This Project' translated font: Preferences standardEToysTitleFont color: textColor1
+ 		}.
+ 	buttonRow := OrderedCollection new.
+ 	buttons do: [:button | buttonRow add: button] separatedBy: [buttonRow add: ((Morph new extent: 30 at 5) color: Color transparent)].
+ 
+ "	addARowCentered: {
+ 			buttons first. 
+ 			(Morph new extent: 30 at 5) color: Color transparent. 
+ 			buttons second.
+ 			(Morph new extent: 30 at 5) color: Color transparent. 
+ 			buttons third
+ 		};"
+ 	window
+ 		addARowCentered: buttonRow;
+ 		addARowCentered: { (window inAColumn: {(ProjectViewMorph on: aProject) lock}) layoutInset: 4};
+ 		addARowCentered: {
+ 			window fancyText: 'Please select a folder' translated font: Preferences standardEToysFont color: textColor1
+ 		};
+ 		addARow: {
+ 			(
+ 				window inAColumn: {
+ 					(pane2 := window inARow: {window inAColumn: {treePane}}) 
+ 						useRoundedCorners;
+ 						layoutInset: 0;
+ 						borderWidth: ColorTheme current dialogPaneBorderWidth;
+ 						borderColor: ColorTheme current dialogPaneBorderColor
+ 				}
+ 			) layoutInset: 10
+ 		}.
+ 	window fullBounds.
+ 	window fillWithRamp: ColorTheme current dialogRampOrColor oriented: 0.65.
+ 	pane2 fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35).
+ "
+ 	buttons do: [ :each |
+ 		each fillWithRamp: ColorTheme current dialogButtonsRampOrColor oriented: (0.75 @ 0).
+ 	].
+ "
+ 	window setProperty: #morphicLayerNumber toValue: 11.
+ 	aFileList postOpen.
+ 	window adoptPaneColor: (Color r: 0.548 g: 0.677 b: 1.0).
+ 	^ window !

Item was added:
+ ----- Method: FileList2 class>>openMorphicViewInWorld (in category 'instance creation') -----
+ openMorphicViewInWorld
+ 	"FileList2 openMorphicViewInWorld"
+ 	^self morphicView openInWorld!

Item was added:
+ ----- Method: FileList2 class>>projectOnlySelectionBlock (in category 'as yet unclassified') -----
+ projectOnlySelectionBlock
+ 
+ 	^[ :entry :myPattern |
+ 		entry isDirectory ifTrue: [
+ 			false
+ 		] ifFalse: [
+ 			#('*.pr' '*.pr.gz' '*.project') anySatisfy: [ :each | each match: entry name]
+ 		]
+ 	]!

Item was added:
+ ----- Method: FileList2 class>>projectOnlySelectionMethod: (in category 'as yet unclassified') -----
+ projectOnlySelectionMethod: incomingEntries
+ 
+ 	| versionsAccepted |
+ 
+ 	"this shows only the latest version of each project"
+ 	versionsAccepted := Dictionary new.
+ 	incomingEntries do: [ :entry | | basicInfoTuple basicVersion basicName |
+ 		entry isDirectory ifFalse: [
+ 			(#('*.pr' '*.pr.gz' '*.project') anySatisfy: [ :each | each match: entry name]) ifTrue: [
+ 				basicInfoTuple := Project parseProjectFileName: entry name.
+ 				basicName := basicInfoTuple first.
+ 				basicVersion := basicInfoTuple second.
+ 				((versionsAccepted includesKey: basicName) and: 
+ 						[(versionsAccepted at: basicName) first > basicVersion]) ifFalse: [
+ 					versionsAccepted at: basicName put: {basicVersion. entry}
+ 				].
+ 			]
+ 		]
+ 	].
+ 	^versionsAccepted asArray collect: [ :each | each second]!

Item was added:
+ ----- Method: FileList2 class>>prototypicalToolWindow (in category 'instance creation') -----
+ prototypicalToolWindow
+ 	"Answer an example of myself seen in a tool window, for the benefit of parts-launching tools"
+ 
+ 	^ self morphicView applyModelExtent!

Item was added:
+ ----- Method: FileList2 class>>selectionBlockForSuffixes: (in category 'as yet unclassified') -----
+ selectionBlockForSuffixes: anArray
+ 
+ 	^[ :entry :myPattern |
+ 		entry isDirectory ifTrue: [
+ 			false
+ 		] ifFalse: [
+ 			anArray anySatisfy: [ :each | each match: entry name]
+ 		]
+ 	]!

Item was added:
+ ----- Method: FileList2 class>>textRow: (in category 'utility') -----
+ textRow: aString 
+ 
+ 	^AlignmentMorph newRow 
+ 		wrapCentering: #center; cellPositioning: #leftCenter;
+ 		color: Color transparent;
+ 		layoutInset: 0;
+ 		addMorph: (
+ 			AlignmentMorph newColumn
+ 			wrapCentering: #center; cellPositioning: #topCenter;
+ 			color: Color transparent;
+ 			vResizing: #shrinkWrap;
+ 			layoutInset: 0;
+ 			addMorph: (
+ 				AlignmentMorph newRow
+ 				wrapCentering: #center; cellPositioning: #leftCenter;
+ 				color: Color transparent;
+ 				hResizing: #shrinkWrap;
+ 				vResizing: #shrinkWrap;
+ 				layoutInset: 0;
+ 				addMorph: ((StringMorph contents: aString) color: Color blue; lock)
+ 			)
+ 		)!

Item was added:
+ ----- Method: FileList2 class>>update:in:fileTypeRow:morphUp: (in category 'morphic ui') -----
+ update: actionRow in: window fileTypeRow: fileTypeRow morphUp: morph
+ 
+ 	| fileTypeInfo info2 buttons textColor1 fileSuffixes fileActions aFileList fileTypeString |
+ 
+ 	(morph notNil and:[(morph valueOfProperty: #enabled) not]) ifTrue: [^self].
+ 	fileTypeRow submorphsDo: [ :sub |
+ 		sub color: (
+ 			sub == morph 
+ 				ifTrue: [Color white] 
+ 				ifFalse: [(sub valueOfProperty: #enabled) 
+ 							ifTrue: [Color transparent] ifFalse: [Color gray]]
+ 		).
+ 	].
+ 	fileTypeString := morph isNil ifTrue:['xxxx'] ifFalse:[morph valueOfProperty: #buttonText].
+ 
+ 	aFileList := window valueOfProperty: #FileList.
+ 	textColor1 := Color r: 0.742 g: 0.839 b: 1.0.
+ 	actionRow removeAllMorphs.
+ 	fileTypeInfo := self endingSpecs.
+ 	info2 := fileTypeInfo detect: [ :each | each first = fileTypeString] ifNone: [ nil ].
+ 	info2 isNil
+ 		ifTrue:[
+ 			buttons := OrderedCollection new
+ 		]
+ 		ifFalse:[
+ 			fileSuffixes := info2 second.
+ 			fileActions := info2 third.
+ 			buttons := fileActions collect: [ :each | aFileList blueButtonForService: each textColor: textColor1 inWindow: window ].
+ 			buttons do: [ :each |
+ 				each fillWithRamp: ColorTheme current okColor oriented: (0.75 @ 0).
+ 			].
+ 		].
+ 	buttons addLast: (self
+ 								blueButtonText: 'Cancel'
+ 								textColor: textColor1
+ 								color: ColorTheme current cancelColor
+ 								inWindow: window
+ 								balloonText: 'Cancel this search' selector: #cancelHit recipient: aFileList).
+ 	buttons do: [ :each | actionRow addMorphBack: each].
+ 	window fullBounds.
+ 	fileSuffixes isNil ifFalse:[
+ 		aFileList fileSelectionBlock: (
+ 			self selectionBlockForSuffixes: (fileSuffixes collect: [ :each | '*.',each])
+ 		).
+ 	].
+ 	aFileList updateFileList.!

Item was added:
+ ----- Method: FileList2>>addNewDirectory (in category 'own services') -----
+ addNewDirectory
+ 	super addNewDirectory.
+ 	self updateDirectory.!

Item was added:
+ ----- Method: FileList2>>blueButtonForService:textColor:inWindow: (in category 'user interface') -----
+ blueButtonForService: aService textColor: textColor inWindow: window 
+ 	| block result |
+ 	block := [self fullName isNil
+ 				ifTrue: [self inform: 'Please select a file' translated]
+ 				ifFalse: [aService performServiceFor: self]].
+ 	result := window
+ 				fancyText: aService buttonLabel capitalized translated
+ 				font: Preferences standardEToysFont
+ 				color: textColor.
+ 	result setProperty: #buttonText toValue: aService buttonLabel capitalized;
+ 		 hResizing: #rigid;
+ 		 extent: 100 @ 20;
+ 		 layoutInset: 4;
+ 		 borderWidth: ColorTheme current dialogButtonBorderWidth;
+ 		 useRoundedCorners;
+ 		 setBalloonText: aService label.
+ 	result
+ 		on: #mouseUp
+ 		send: #value
+ 		to: block.
+ 	^ result!

Item was added:
+ ----- Method: FileList2>>cancelHit (in category 'private') -----
+ cancelHit
+ 
+ 	modalView delete.
+ 	directory := fileName := currentDirectorySelected := nil.!

Item was added:
+ ----- Method: FileList2>>changeDirectoryTo: (in category 'volume list and pattern') -----
+ changeDirectoryTo: aFileDirectory
+ 	"Change directory as requested."
+ 
+ 	self directory: aFileDirectory.
+ 	self updateDirectory!

Item was added:
+ ----- Method: FileList2>>currentDirectorySelected (in category 'private') -----
+ currentDirectorySelected
+ 	^ currentDirectorySelected
+ !

Item was added:
+ ----- Method: FileList2>>deleteDirectory (in category 'own services') -----
+ deleteDirectory
+ 	super deleteDirectory.
+ 	self updateDirectory.!

Item was added:
+ ----- Method: FileList2>>dirSelectionBlock: (in category 'initialization') -----
+ dirSelectionBlock: aBlock
+ 	dirSelectionBlock := aBlock!

Item was added:
+ ----- Method: FileList2>>directory (in category 'volume list and pattern') -----
+ directory
+ 
+ 	^directory!

Item was added:
+ ----- Method: FileList2>>directory: (in category 'initialization') -----
+ directory: dir
+ 	"Set the path of the volume to be displayed."
+ 
+ 	self okToChange ifFalse: [^ self].
+ 
+ 	self modelSleep.
+ 	directory := dir.
+ 	self modelWakeUp.
+ 
+ 	sortMode == nil ifTrue: [sortMode := #date].
+ 	volList := Array with: '[]'.
+ 	directory ifNotNil: [
+ 		volList := volList, directory pathParts.  "Nesting suggestion from RvL"
+ 	].
+ 	volList := volList withIndexCollect: [:each :i | ( String new: i-1 withAll: $ ), each].
+ 	self changed: #relabel.
+ 	self changed: #volumeList.
+ 	self pattern: pattern.
+ 	directoryChangeBlock ifNotNil: [directoryChangeBlock value: directory].!

Item was added:
+ ----- Method: FileList2>>directoryChangeBlock: (in category 'initialization') -----
+ directoryChangeBlock: aBlockOrNil
+ 
+ 	directoryChangeBlock := aBlockOrNil.!

Item was added:
+ ----- Method: FileList2>>directoryNamesFor: (in category 'private') -----
+ directoryNamesFor: item
+ 	"item may be file directory or server directory"
+ 	| entries |
+ 	entries := item directoryNames.
+ 	dirSelectionBlock ifNotNil:[entries := entries select: dirSelectionBlock].
+ 	^entries!

Item was added:
+ ----- Method: FileList2>>dropDestinationDirectory:event: (in category 'drag''n''drop') -----
+ dropDestinationDirectory: dest event: evt
+ 	"Answer a FileDirectory representing the drop destination in the directory hierarchy morph dest"
+ self isThisEverCalled.
+ 	^ (dest itemFromPoint: evt position) withoutListWrapper!

Item was added:
+ ----- Method: FileList2>>fileSelectionBlock: (in category 'initialization') -----
+ fileSelectionBlock: aBlock
+ 
+ 	fileSelectionBlock := aBlock!

Item was added:
+ ----- Method: FileList2>>getSelectedDirectory (in category 'private') -----
+ getSelectedDirectory
+ 	ok == true ifFalse: [^ nil].
+ 	^ currentDirectorySelected
+ !

Item was added:
+ ----- Method: FileList2>>getSelectedFile (in category 'private') -----
+ getSelectedFile
+ 	"Answer a filestream on the selected file.  If it cannot be opened for read/write, try read-only before giving up; answer nil if unsuccessful"
+ 
+ 	ok == true ifFalse: [^ nil].
+ 	directory ifNil: [^ nil].
+ 	fileName ifNil: [^ nil].
+ 	^ (directory oldFileNamed: fileName) ifNil:
+ 		[directory readOnlyFileNamed: fileName]!

Item was added:
+ ----- Method: FileList2>>importImage (in category 'own services') -----
+ importImage
+ 	"Import the given image file and store the resulting Form in the default Imports"
+ 
+ 	| fname image |
+ 	fname := fileName sansPeriodSuffix.
+ 	image := Form fromFileNamed: self fullName.
+ 	Imports default importImage: image named: fname.
+ !

Item was added:
+ ----- Method: FileList2>>initialDirectoryList (in category 'initialization') -----
+ initialDirectoryList
+ 
+ 	| dirList |
+ 	dirList := (FileDirectory on: '') directoryNames collect: [ :each |
+ 		FileDirectoryWrapper with: (FileDirectory on: each) name: each model: self].
+ 	dirList isEmpty ifTrue:[
+ 		dirList := Array with: (FileDirectoryWrapper 
+ 			with: FileDirectory default 
+ 			name: FileDirectory default localName 
+ 			model: self)].
+ 	dirList := dirList,(
+ 		ServerDirectory serverNames collect: [ :n | | nameToShow dir | 
+ 			dir := ServerDirectory serverNamed: n.
+ 			nameToShow := n.
+ 			(dir directoryWrapperClass with: dir name: nameToShow model: self)
+ 				balloonText: dir realUrl
+ 		]
+ 	).
+ 	^dirList!

Item was added:
+ ----- Method: FileList2>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	super initialize.
+ 	showDirsInFileList := false.
+ 	fileSelectionBlock := [ :entry :myPattern |
+ 		entry isDirectory ifTrue: [
+ 			showDirsInFileList
+ 		] ifFalse: [
+ 			myPattern = '*' or: [myPattern match: entry name]
+ 		]
+ 	].
+ 	dirSelectionBlock := [ :dirName | true].!

Item was added:
+ ----- Method: FileList2>>isDirectoryList: (in category 'drag''n''drop') -----
+ isDirectoryList: aMorph
+ 	^aMorph isKindOf: SimpleHierarchicalListMorph!

Item was added:
+ ----- Method: FileList2>>labelString (in category 'initialization') -----
+ labelString
+ 	^ (directory ifNil: [^'[]']) pathName contractTo: 50!

Item was added:
+ ----- Method: FileList2>>limitedSuperSwikiDirectoryList (in category 'initialization') -----
+ limitedSuperSwikiDirectoryList
+ 
+ 	| dirList localDirName localDir |
+ 
+ 	dirList := OrderedCollection new.
+ 	ServerDirectory serverNames do: [ :n | | dir nameToShow | 
+ 		dir := ServerDirectory serverNamed: n.
+ 		dir isProjectSwiki ifTrue: [
+ 			nameToShow := n.
+ 			dirList add: ((dir directoryWrapperClass with: dir name: nameToShow model: self)
+ 				balloonText: dir realUrl)
+ 		].
+ 	].
+ 	ServerDirectory localProjectDirectories do: [ :each |
+ 		dirList add: (FileDirectoryWrapper with: each name: each localName model: self)
+ 	].
+ 	"Make sure the following are always shown, but not twice"
+ 	localDirName := SecurityManager default untrustedUserDirectory.
+ 	localDir := FileDirectory on: localDirName.
+ 	((ServerDirectory localProjectDirectories collect: [:each | each pathName]) includes: localDirName)
+ 			ifFalse: [dirList add: (FileDirectoryWrapper with: localDir name: localDir localName model: self)].
+ 	FileDirectory default pathName = localDirName
+ 			ifFalse: [dirList add: (FileDirectoryWrapper with: FileDirectory default name: FileDirectory default localName model: self)].
+ 	(dirList anySatisfy: [:each | each withoutListWrapper acceptsUploads])
+ 		ifFalse: [dirList add: (FileDirectoryWrapper with: FileDirectory default name: FileDirectory default localName model: self)].
+ 	^dirList!

Item was added:
+ ----- Method: FileList2>>limitedSuperSwikiPublishDirectoryList (in category 'initialization') -----
+ limitedSuperSwikiPublishDirectoryList
+ 
+ 	| dirList localDirName localDir |
+ 
+ 	dirList := self publishingServers.
+ 	ServerDirectory localProjectDirectories do: [ :each |
+ 		dirList add: (FileDirectoryWrapper with: each name: each localName model: self)].
+ 
+ 	"Make sure the following are always shown, but not twice"
+ 	localDirName := SecurityManager default untrustedUserDirectory.
+ 	localDir := FileDirectory on: localDirName.
+ 	((ServerDirectory localProjectDirectories collect: [:each | each pathName]) includes: localDirName)
+ 			ifFalse: [dirList add: (FileDirectoryWrapper with: localDir name: localDir localName model: self)].
+ 	FileDirectory default pathName = localDirName
+ 			ifFalse: [dirList add: (FileDirectoryWrapper with: FileDirectory default name: FileDirectory default localName model: self)].
+ 	^dirList!

Item was added:
+ ----- Method: FileList2>>listForPattern: (in category 'volume list and pattern') -----
+ listForPattern: pat
+ 	"Make the list be those file names which match the pattern."
+ 
+ 	| sizePad newList entries |
+ 	directory ifNil: [^#()].
+ 	entries := (Preferences eToyLoginEnabled
+ 		and: [Utilities authorNamePerSe notNil])
+ 		ifTrue: [directory matchingEntries: {'submittedBy: ' , Utilities authorName.} ]
+ 		ifFalse: [directory entries].
+ 	(fileSelectionBlock isKindOf: MessageSend) ifTrue: [
+ 		fileSelectionBlock arguments: {entries}.
+ 		newList := fileSelectionBlock value.
+ 		fileSelectionBlock arguments: #().
+ 	] ifFalse: [
+ 		newList := entries select: [:entry | fileSelectionBlock value: entry value: pat].
+ 	].
+ 	newList := newList asArray sort: self sortBlock.
+ 	sizePad := (newList inject: 0 into: [:mx :entry | mx max: entry fileSize])
+ 					asStringWithCommas size - 1.
+ 	^newList collect: [ :e | self fileNameFormattedFrom: e sizePad: sizePad ]!

Item was added:
+ ----- Method: FileList2>>listForPatterns: (in category 'volume list and pattern') -----
+ listForPatterns: anArray
+ 	"Make the list be those file names which match the patterns."
+ 
+ 	| sizePad newList |
+ 	directory ifNil: [^#()].
+ 	(fileSelectionBlock isKindOf: MessageSend) ifTrue: [
+ 		fileSelectionBlock arguments: {directory entries}.
+ 		newList := fileSelectionBlock value.
+ 		fileSelectionBlock arguments: #().
+ 	] ifFalse: [
+ 		newList := Set new.
+ 		anArray do: [ :pat |
+ 			newList addAll: (directory entries select: [:entry | fileSelectionBlock value: entry value: pat]) ].
+ 	].
+ 	newList := newList asArray sort: self sortBlock.
+ 	sizePad := (newList inject: 0 into: [:mx :entry | mx max: entry fileSize])
+ 					asStringWithCommas size.
+ 	^newList collect: [ :e | self fileNameFormattedFrom: e sizePad: sizePad ]!

Item was added:
+ ----- Method: FileList2>>modalView: (in category 'private') -----
+ modalView: aSystemWindowOrSuch
+ 
+ 	modalView := aSystemWindowOrSuch!

Item was added:
+ ----- Method: FileList2>>morphicDirectoryTreePane (in category 'user interface') -----
+ morphicDirectoryTreePane
+ 
+ 	^self morphicDirectoryTreePaneFiltered: #initialDirectoryList
+ !

Item was added:
+ ----- Method: FileList2>>morphicDirectoryTreePaneFiltered: (in category 'user interface') -----
+ morphicDirectoryTreePaneFiltered: aSymbol
+ 	^(SimpleHierarchicalListMorph 
+ 		on: self
+ 		list: aSymbol
+ 		selected: #currentDirectorySelected
+ 		changeSelected: #setSelectedDirectoryTo:
+ 		menu: #volumeMenu:
+ 		keystroke: nil)
+ 			autoDeselect: false;
+ 			enableDrag: false;
+ 			enableDrop: true;
+ 			yourself
+ 		
+ !

Item was added:
+ ----- Method: FileList2>>morphicFileContentsPane (in category 'user interface') -----
+ morphicFileContentsPane
+ 
+ 	^PluggableTextMorph 
+ 		on: self 
+ 		text: #contents 
+ 		accept: #put:
+ 		readSelection: #contentsSelection 
+ 		menu: #fileContentsMenu:shifted:
+ !

Item was added:
+ ----- Method: FileList2>>morphicFileListPane (in category 'user interface') -----
+ morphicFileListPane
+ 
+ 	^(PluggableListMorph 
+ 		on: self 
+ 		list: #fileList 
+ 		selected: #fileListIndex
+ 		changeSelected: #fileListIndex: 
+ 		menu: #fileListMenu:)
+ 			enableDrag: true;
+ 			enableDrop: false;
+ 			yourself
+ 
+ !

Item was added:
+ ----- Method: FileList2>>morphicPatternPane (in category 'user interface') -----
+ morphicPatternPane
+    | pane |
+     pane := PluggableTextMorph 
+ 		on: self 
+ 		text: #pattern 
+ 		accept: #pattern:.
+     pane acceptOnCR: true.
+    ^pane
+ 		
+ !

Item was added:
+ ----- Method: FileList2>>okHit (in category 'private') -----
+ okHit
+ 
+ 	ok := true.
+ 	currentDirectorySelected
+ 		ifNil: [ Beeper beep ]
+ 		ifNotNil: [
+ 			self class lastSelDir: directory.
+ 			modalView delete ]!

Item was added:
+ ----- Method: FileList2>>okHitForProjectLoader (in category 'private') -----
+ okHitForProjectLoader
+ 
+ 	| areaOfProgress |
+ 	fileName ifNil: [^ self].
+ 	ok := true.
+ 	areaOfProgress := modalView firstSubmorph.
+ 	[
+ 		areaOfProgress setProperty: #deleteOnProgressCompletion toValue: modalView.
+ 		self openProjectFromFile.
+ 		modalView delete.	"probably won't get here"
+ 	]
+ 		on: ProgressTargetRequestNotification
+ 		do: [ :ex | ex resume: areaOfProgress].
+ 
+ 
+ !

Item was added:
+ ----- Method: FileList2>>okayAndCancelServices (in category 'own services') -----
+ okayAndCancelServices
+ 	"Answer ok and cancel services"
+ 
+ 	^ {self serviceOkay. self serviceCancel}!

Item was added:
+ ----- Method: FileList2>>openImageInWindow (in category 'own services') -----
+ openImageInWindow
+ 	"Handle five file formats: GIF, JPG, PNG, Form stoteOn: (run coded), and BMP.
+ 	Fail if file format is not recognized."
+ 
+ 	| image myStream |
+ 	myStream := (directory readOnlyFileNamed: fileName) binary.
+ 	[image := Form fromBinaryStream: myStream.
+ 	Project current openImage: image name: fileName saveResource: false]
+ 		ensure: [myStream close]
+ !

Item was added:
+ ----- Method: FileList2>>openProjectFromFile (in category 'own services') -----
+ openProjectFromFile
+ 	"Reconstitute a Morph from the selected file, presumed to be represent
+ 	a Morph saved via the SmartRefStream mechanism, and open it in an
+ 	appropriate Morphic world."
+ 
+ 	Project canWeLoadAProjectNow ifFalse: [^ self].
+ 	ProjectViewMorph 
+ 		openFromDirectory: directory 
+ 		andFileName: fileName
+ !

Item was added:
+ ----- Method: FileList2>>optionalButtonRow (in category 'initialization') -----
+ optionalButtonRow
+ 	"Answer the button row associated with a file list"
+ 
+ 	| aRow |
+ 	aRow := AlignmentMorph newRow beSticky.
+ 	aRow color: Color transparent.
+ 	aRow clipSubmorphs: true.
+ 	aRow layoutInset: 5 at 1; cellInset: 6.
+ 	self universalButtonServices do:  "just the three sort-by items"
+ 			[:service |
+ 				aRow addMorphBack: (service buttonToTriggerIn: self).
+ 				(service selector  == #sortBySize)
+ 					ifTrue:
+ 						[aRow addTransparentSpacerOfSize: (4 at 0)]].
+ 	aRow setNameTo: 'buttons'.
+ 	aRow setProperty: #buttonRow toValue: true.  "Used for dynamic retrieval later on"
+ 	^ aRow!

Item was added:
+ ----- Method: FileList2>>optionalButtonSpecs (in category 'initialization') -----
+ optionalButtonSpecs
+ 
+ 	^optionalButtonSpecs ifNil: [super optionalButtonSpecs]!

Item was added:
+ ----- Method: FileList2>>optionalButtonSpecs: (in category 'initialization') -----
+ optionalButtonSpecs: anArray
+ 
+ 	optionalButtonSpecs := anArray!

Item was added:
+ ----- Method: FileList2>>postOpen (in category 'private') -----
+ postOpen
+ 
+ 	directory ifNotNil: [
+ 		self changed: #(openPath) , directory pathParts. 
+ 	].
+ !

Item was added:
+ ----- Method: FileList2>>publishingServers (in category 'initialization') -----
+ publishingServers
+ 
+ 	| dirList |
+ 
+ 	dirList := OrderedCollection new.
+ 	ServerDirectory serverNames do: [ :n | | dir nameToShow | 
+ 		dir := ServerDirectory serverNamed: n.
+ 		(dir isProjectSwiki and: [dir acceptsUploads])
+ 			 ifTrue: [
+ 				nameToShow := n.
+ 				dirList add: ((dir directoryWrapperClass with: dir name: nameToShow model: self)
+ 					balloonText: dir realUrl)]].
+ 	^dirList!

Item was added:
+ ----- Method: FileList2>>removeLinefeeds (in category 'own services') -----
+ removeLinefeeds
+ 	"Remove any line feeds by converting to CRs instead.  This is a temporary implementation for 3.6 only... should be removed during 3.7alpha."
+ 	| fileContents |
+ 	fileContents := ((FileStream readOnlyFileNamed: self fullName) wantsLineEndConversion: true) contentsOfEntireFile.
+ 	(FileStream newFileNamed: self fullName) 
+ 		nextPutAll: fileContents;
+ 		close.!

Item was added:
+ ----- Method: FileList2>>saveLocalOnlyHit (in category 'private') -----
+ saveLocalOnlyHit
+ 	ok := true.
+ 	modalView delete.
+ 	directory := fileName := nil.
+ 	currentDirectorySelected := #localOnly.!

Item was added:
+ ----- Method: FileList2>>serviceCancel (in category 'own services') -----
+ serviceCancel
+ 	"Answer a service for hitting the cancel button"
+ 
+ 	^ (SimpleServiceEntry new
+ 		provider: self label: 'cancel' selector: #cancelHit 
+ 		description: 'hit here to cancel ')
+ 		buttonLabel: 'cancel'!

Item was added:
+ ----- Method: FileList2>>serviceOkay (in category 'own services') -----
+ serviceOkay
+ 	"Answer a service for hitting the okay button"
+ 
+ 	^ (SimpleServiceEntry new
+ 		provider: self label: 'okay' selector: #okHit 
+ 		description: 'hit here to accept the current selection')
+ 		buttonLabel: 'ok'!

Item was added:
+ ----- Method: FileList2>>serviceOpenProjectFromFile (in category 'own services') -----
+ serviceOpenProjectFromFile
+ 	"Answer a service for opening a .pr project file"
+ 
+ 	^ SimpleServiceEntry 
+ 		provider: self 
+ 		label: 'load as project'
+ 		selector: #openProjectFromFile
+ 		description: 'open project from file'
+ 		buttonLabel: 'load'!

Item was added:
+ ----- Method: FileList2>>servicesForFolderSelector (in category 'own services') -----
+ servicesForFolderSelector
+ 	"Answer the ok and cancel servies for the folder selector"
+ 
+ 	^ self okayAndCancelServices!

Item was added:
+ ----- Method: FileList2>>servicesForProjectLoader (in category 'own services') -----
+ servicesForProjectLoader
+ 	"Answer the services to show in the button pane for the project loader"
+ 
+ 	^ {self serviceSortByName. self serviceSortByDate. self serviceSortBySize. self serviceOpenProjectFromFile}!

Item was added:
+ ----- Method: FileList2>>setSelectedDirectoryTo: (in category 'private') -----
+ setSelectedDirectoryTo: aFileDirectoryWrapper
+ 	currentDirectorySelected := aFileDirectoryWrapper.
+ 	self directory: aFileDirectoryWrapper withoutListWrapper.
+ 	brevityState := #FileList.
+ 	"self addPath: path."
+ 	self changed: #fileList.
+ 	self changed: #contents.
+ 	self changed: #currentDirectorySelected.!

Item was added:
+ ----- Method: FileList2>>specsForImageViewer (in category 'as yet unclassified') -----
+ specsForImageViewer
+ 
+ 	 ^{self serviceSortByName. self serviceSortByDate. self serviceSortBySize }!

Item was added:
+ ----- Method: FileList2>>universalButtonServices (in category 'initialization') -----
+ universalButtonServices
+ 	"Answer the services to be reflected in the receiver's buttons"
+ 
+ 	^ self optionalButtonSpecs!

Item was added:
+ ----- Method: FileList2>>updateDirectory (in category 'initialization') -----
+ updateDirectory
+ 	"directory has been changed externally, by calling directory:.
+ 	Now change the view to reflect the change."
+ 	self changed: #currentDirectorySelected.
+ 	self postOpen.!



More information about the Squeak-dev mailing list