Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
ReleaseBuilderSqueakland new buildInitialScreen
Last updated at 10:26 am UTC on 14 October 2017
 ReleaseBuilder subclass: #ReleaseBuilderSqueakland
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Etoys-ReleaseBuilder'


 buildInitialScreen
	"ReleaseBuilderSqueakland new buildInitialScreen"

	QuickGuideMorph preloadIndexPage.

	World
		submorphsDo: [:m | m delete].
	Flaps disableGlobalFlaps: false.
	Flaps enableEToyFlaps.

	ProjectLoading loadFromImagePath: 'Tutorials'.
	ProjectLoading loadFromImagePath: 'Gallery'.
	ProjectLoading loadFromImagePath: 'Home'.

	(World submorphs select: [:e | e isMemberOf: ProjectViewMorph]) do: [:e | e delete].
	Project current
		setThumbnail: (Project home ifNotNilDo: [:p | p thumbnail]).


configureDesktop

	super configureDesktop.
	self loadDefaultForms.
	self setDisplayExtent: 1200@900.
	EtoysTheme create apply.



Squeakland version has

loadFromImagePath: projectName 
	"Open the project in image path. This is used with projects in OLPC distribution.
	- The image's directory is used.
	- Squeaklets directory is ignored.
	- If there is a project named projectName, it is opened.
	"
	"self openFromImagePath: 'Welcome'"
	| directory aStream entries fileName |
	(Project named: projectName)
		ifNotNilDo: [:project | ^ project].
	directory := FileDirectory on: Smalltalk imagePath.
	entries := FileList2 projectOnlySelectionMethod: directory entries.
	fileName := (entries
		detect: [:each | (Project parseProjectFileName: each name) first = projectName]
		ifNone: [^ nil]) name.
	self
		showProgressBarDuring: [ProgressNotification signal: '0'.
			directory := FileDirectory on: Smalltalk imagePath.
			aStream := directory readOnlyFileNamed: fileName.
			^ self
				loadName: fileName
				stream: aStream
				fromDirectory: directory
				withProjectView: nil]