Squeak
  QotD    "To be or not to be" – Shakespeare
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
ProjectLoading steps
Last updated at 1:48 pm UTC on 29 June 2018
The steps for loading a Project, which constitute the main program for this issue, so to say, are in the class method

    #openName:stream:fromDirectory:withProjectView:clearOriginFlag:
of the class ProjectLoading.

This class has no instance methods, thus actually the class object (class name ProjectLoading) does the job of loading a project saved in a pr file.



The "main program" for loading projects



 ProjectLoading
 openName: aFileName 
 stream: preStream 
 fromDirectory: aDirectoryOrNil
 withProjectView: existingView 
 clearOriginFlag: clearOriginFlag




 	"Reconstitute a Morph from the selected file, presumed to
 represent a Morph saved via the SmartRefStream mechanism, and open it
 in an appropriate Morphic world."
 
    	| morphOrList archive mgr substituteFont numberOfFontSubstitutes resultArray anObject project manifests dict |



 	(self checkStream: preStream) ifTrue: [^ self].



0.2

 	ProgressNotification signal: '0.2'.

 	archive := preStream isZipArchive
 		ifTrue:[ZipArchive new readFrom: preStream]
 		ifFalse:[nil].
 	archive ifNotNil:[
 	manifests := (archive membersMatching: 'manifest').
 	(manifests size = 1 and: [((dict := self parseManifest: manifests first contents) at: 'Project-Format' ifAbsent: []) = 'S-Expression'])
 		ifTrue: [
 			^ (self respondsTo: #openSexpProjectDict:stream:fromDirectory:withProjectView:)
 				ifTrue: [self openSexpProjectDict: dict stream: preStream fromDirectory: aDirectoryOrNil withProjectView: existingView]
 				ifFalse: [self inform: 'Cannot load S-Expression format projects without Etoys' translated]]].
 


 	morphOrList := self morphOrList: aFileName stream: preStream fromDirectory: aDirectoryOrNil archive: archive.

 	morphOrList ifNil: [^ self].





0.4

 	ProgressNotification  signal: '0.4'.

 	resultArray := self fileInName: aFileName archive: archive morphOrList: morphOrList.

 	anObject := resultArray first.
 	numberOfFontSubstitutes := resultArray second.
 	substituteFont := resultArray third.
 	mgr := resultArray fourth.

 	preStream close.






0.7

 	ProgressNotification  signal: '0.7'.

 		"the hard part is over"
 	(anObject isKindOf: ImageSegment) ifTrue: [

 		project := self loadImageSegment: anObject
 			fromDirectory: aDirectoryOrNil
 			withProjectView: existingView
 			numberOfFontSubstitutes: numberOfFontSubstitutes
 			substituteFont: substituteFont
 			mgr: mgr.

 		project noteManifestDetailsIn: dict.

 		project removeParameter: #sugarProperties.

 		Smalltalk at: #SugarPropertiesNotification ifPresent: [:sp |
 			sp signal ifNotNil: [:props | 
 				project keepSugarProperties: props monitor: true]].
 		clearOriginFlag ifTrue: [project forgetExistingURL].





0.8

 		ProgressNotification  signal: '0.8'.

 			^ project
 				ifNil: [self inform: 'No project found in this file' translated]
 				ifNotNil: [ProjectEntryNotification signal: project]].



Project current openViewAndEnter: anObject