[squeak-dev] The Trunk: MorphicExtras-mt.278.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Oct 14 12:04:20 UTC 2020


Marcel Taeumel uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-mt.278.mcz

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

Name: MorphicExtras-mt.278
Author: mt
Time: 14 October 2020, 2:04:17.592569 pm
UUID: 0cffdb2f-a95d-164b-8c55-7f22312685dc
Ancestors: MorphicExtras-mt.277

Rename #doWithIndex: to #withIndexDo:. See http://forum.world.st/The-Inbox-60Deprecated-ct-80-mcz-td5120706.html

=============== Diff against MorphicExtras-mt.277 ===============

Item was changed:
  ----- Method: BookMorph>>acceptSortedContentsFrom: (in category 'sorting') -----
  acceptSortedContentsFrom: aHolder 
  	"Update my page list from the given page sorter."
  
  	| goodPages rejects |
  	goodPages := OrderedCollection new.
  	rejects := OrderedCollection new.
+ 	aHolder submorphs withIndexDo: 
- 	aHolder submorphs doWithIndex: 
  			[:m :i | | toAdd sqPage | 
  			toAdd := nil.
  			(m isKindOf: PasteUpMorph) ifTrue: [toAdd := m].
  			(m isKindOf: BookPageThumbnailMorph) 
  				ifTrue: 
  					[toAdd := m page.
  					m bookMorph == self 
  						ifFalse: 
  							["borrowed from another book. preserve the original"
  
  							toAdd := toAdd veryDeepCopy.
  
  							"since we came from elsewhere, cached strings are wrong"
  							self removeProperty: #allTextUrls.
  							self removeProperty: #allText]].
  			toAdd isString 
  				ifTrue: 
  					["a url"
  
  					toAdd := pages detect: [:aPage | aPage url = toAdd] ifNone: [toAdd]].
  			toAdd isString 
  				ifTrue: 
  					[sqPage := SqueakPageCache atURL: toAdd.
  					toAdd := sqPage contentsMorph 
  								ifNil: [sqPage copyForSaving	"a MorphObjectOut"]
  								ifNotNil: [sqPage contentsMorph]].
  			toAdd ifNil: [rejects add: m] ifNotNil: [goodPages add: toAdd]].
  	self newPages: goodPages.
  	goodPages isEmpty ifTrue: [self insertPage].
  	rejects notEmpty 
  		ifTrue: 
  			[self 
  				inform: rejects size printString , ' objects vanished in this process.']!

Item was changed:
  ----- Method: BookMorph>>getAllText (in category 'menu') -----
  getAllText
  	"Collect the text for each page.  Just point at strings so don't have to recopy them.  Parallel array of urls for ID of pages.
  	allText = Array (pages size) of arrays (fields in it) of strings of text.
  	allTextUrls = Array (pages size) of urls or page numbers.
  	For any page that is out, text data came from .bo file on server.  
  	Is rewritten when one or all pages are stored."
  
  	| oldUrls oldStringLists allText allTextUrls |
  	oldUrls := self valueOfProperty: #allTextUrls ifAbsent: [#()].
  	oldStringLists := self valueOfProperty: #allText ifAbsent: [#()].
  	allText := pages collect: [:pg | OrderedCollection new].
  	allTextUrls := Array new: pages size.
+ 	pages withIndexDo: [:aPage :ind | | which aUrl |
- 	pages doWithIndex: [:aPage :ind | | which aUrl |
  		aUrl := aPage url.  aPage isInMemory 
  			ifTrue: [(allText at: ind) addAll: (aPage allStringsAfter: nil).
  				aUrl ifNil: [aUrl := ind].
  				allTextUrls at: ind put: aUrl]
  			ifFalse: ["Order of pages on server may be different.  (later keep up to date?)"
  				which := oldUrls indexOf: aUrl.
  				allTextUrls at: ind put: aUrl.
  				which = 0 ifFalse: [allText at: ind put: (oldStringLists at: which)]]].
  	self setProperty: #allText toValue: allText.
  	self setProperty: #allTextUrls toValue: allTextUrls.
  	^ allText!

Item was changed:
  ----- Method: BookMorph>>getStemUrl (in category 'menu') -----
  getStemUrl
  	"Try to find the old place where this book was stored. Confirm with the 
  	user. Else ask for new place."
  	| initial pg url knownURL |
  
  	knownURL := false.
  	initial := ''.
  	(pg := currentPage valueOfProperty: #SqueakPage)
  		ifNotNil: [pg contentsMorph == currentPage
  				ifTrue: [initial := pg url.
  					knownURL := true]].
  	"If this page has a url"
  	pages
+ 		withIndexDo: [:aPage :ind | initial isEmpty
- 		doWithIndex: [:aPage :ind | initial isEmpty
  				ifTrue: [aPage isInMemory
  						ifTrue: [(pg := aPage valueOfProperty: #SqueakPage)
  								ifNotNil: [initial := pg url]]]].
  	"any page with a url"
  	initial isEmpty
  		ifTrue: [initial := ServerDirectory defaultStemUrl , '1.sp'].
  	"A new legal place"
  	url := knownURL
  		ifTrue: [initial]
  		ifFalse: [UIManager default request: 'url of the place to store a typical page in this book.
  Must begin with file:// or ftp://' translated initialAnswer: initial].
  	^ SqueakPage stemUrl: url!

Item was changed:
  ----- Method: BookMorph>>reserveUrls (in category 'menu') -----
  reserveUrls
  	"Save a dummy version of the book first, assign all pages URLs, write dummy files to reserve the url, and write the index.  Good when I have pages with interpointing bookmarks."
  
  	| stem |
  	(stem := self getStemUrl) isEmpty ifTrue: [^self].
+ 	pages withIndexDo: 
- 	pages doWithIndex: 
  			[:pg :ind | 
  			"does write the current page too"
  
  			pg url ifNil: [pg reserveUrl: stem , ind printString , '.sp']]
  
  	"self saveIndexOnURL."!

Item was changed:
  ----- Method: BookMorph>>saveAsNumberedURLs (in category 'menu') -----
  saveAsNumberedURLs
  	"Write out all pages in this book that are not showing, onto a server.  The local disk could be the server.  For any page that does not have a SqueakPage and a url already, name that page file by its page number.  Any pages that are already totally out will stay that way."
  
  	| stem list firstTime |
  	firstTime := (self valueOfProperty: #url) isNil.
  	stem := self getStemUrl.	"user must approve"
  	stem isEmpty ifTrue: [^self].
  	firstTime ifTrue: [self setProperty: #futureUrl toValue: stem , '.bo'].
  	self reserveUrlsIfNeeded.
+ 	pages withIndexDo: 
- 	pages doWithIndex: 
  			[:aPage :ind | 
  			"does write the current page too"
  
  			aPage isInMemory 
  				ifTrue: 
  					["not out now"
  
  					aPage presenter ifNotNil: [aPage presenter flushPlayerListCache].
  					aPage saveOnURL: stem , ind printString , '.sp']].
  	list := pages collect: [:aPage | aPage sqkPage prePurge].
  	"knows not to purge the current page"
  	list := (list select: [:each | each notNil]) asArray.
  	"do bulk become:"
  	(list collect: [:each | each contentsMorph]) 
  		elementsExchangeIdentityWith: (list 
  				collect: [:spg | MorphObjectOut new xxxSetUrl: spg url page: spg]).
  	self saveIndexOnURL.
  	self presenter ifNotNil: [self presenter flushPlayerListCache].
  	firstTime 
  		ifTrue: 
  			["Put a thumbnail into the hand"
  
  			URLMorph grabForBook: self.
  			self setProperty: #futureUrl toValue: nil	"clean up"]!

Item was changed:
  ----- Method: BookMorph>>saveIndexOnURL (in category 'menu') -----
  saveIndexOnURL
  	"Make up an index to the pages of this book, with thumbnails, and store it on the server.  (aDictionary, aMorphObjectOut, aMorphObjectOut, aMorphObjectOut).  The last part corresponds exactly to what pages looks like when they are all out.  Each holds onto a SqueakPage, which holds a url and a thumbnail."
  
  	| dict mine sf urlList list |
  	pages isEmpty ifTrue: [^self].
  	dict := Dictionary new.
  	dict at: #modTime put: Time totalSeconds.
  	"self getAllText MUST have been called at start of this operation."
  	dict at: #allText put: (self valueOfProperty: #allText).
  	#(#color #borderWidth #borderColor #pageSize) 
  		do: [:sel | dict at: sel put: (self perform: sel)].
  	self reserveUrlsIfNeeded.	"should already be done"
  	list := pages copy.	"paste dict on front below"
  	"Fix up the entries, should already be done"
+ 	list withIndexDo: 
- 	list doWithIndex: 
  			[:out :ind | 
  			out isInMemory 
  				ifTrue: 
  					[(out valueOfProperty: #SqueakPage) ifNil: [out saveOnURLbasic].
  					list at: ind put: out sqkPage copyForSaving]].
  	urlList := list collect: [:ppg | ppg url].
  	self setProperty: #allTextUrls toValue: urlList.
  	dict at: #allTextUrls put: urlList.
  	list := (Array with: dict) , list.
  	mine := self valueOfProperty: #url.
  	mine ifNil: 
  			[mine := self getStemUrl , '.bo'.
  			self setProperty: #url toValue: mine].
  	sf := ServerDirectory new fullPath: mine.
  	Cursor wait showWhile: 
  			[ | remoteFile |
  			remoteFile := sf fileNamed: mine.
  			remoteFile dataIsValid.
  			remoteFile fileOutClass: nil andObject: list
  			"remoteFile close"]!

Item was changed:
  ----- Method: InternalThreadNavigationMorph>>acceptSortedContentsFrom: (in category 'sorting') -----
  acceptSortedContentsFrom: aHolder
  	"Update my page list from the given page sorter."
  
  	
  
  	threadName isEmpty ifTrue: [threadName := 'I need a name' translated].
  	threadName := UIManager default 
  		request: 'Name this thread.' translated 
  		initialAnswer: threadName.
  	threadName isEmptyOrNil ifTrue: [^self].
  	listOfPages := OrderedCollection new.
+ 	aHolder submorphs withIndexDo: [:m :i | | cachedData proj nameOfThisProject |
- 	aHolder submorphs doWithIndex: [:m :i | | cachedData proj nameOfThisProject |
  		(nameOfThisProject := m valueOfProperty: #nameOfThisProject) ifNotNil: [
  			cachedData := {nameOfThisProject}.
  			proj := Project named: nameOfThisProject.
  			(proj isNil or: [proj thumbnail isNil]) ifFalse: [
  				cachedData := cachedData, {proj thumbnail scaledToSize: self myThumbnailSize}.
  			].
  			listOfPages add: cachedData.
  		].
  	].
  	self class know: listOfPages as: threadName.
  	self removeAllMorphs; addButtons.
  	self world ifNil: [
  		self openInWorld; positionAppropriately.
  	].
  !

Item was changed:
  ----- Method: TabSorterMorph>>acceptSort (in category 'buttons') -----
  acceptSort
  	"Reconstitute the palette based on what is found in the sorter"
  
  	| rejects oldOwner tabsToUse oldTop |
  	tabsToUse := OrderedCollection new.
  	rejects := OrderedCollection new.
+ 	pageHolder submorphs withIndexDo: 
- 	pageHolder submorphs doWithIndex: 
  			[:m :i | | appearanceMorph toAdd aMenu | 
  			toAdd := nil.
  			(m isKindOf: BookMorph) ifTrue: [toAdd := SorterTokenMorph forMorph: m].
  			(m isKindOf: SorterTokenMorph) 
  				ifTrue: 
  					[toAdd := m morphRepresented.
  					(toAdd referent isKindOf: MenuMorph) 
  						ifTrue: 
  							[(aMenu := toAdd referent) setProperty: #paletteMenu toValue: true.
  							(aMenu submorphs size > 1 and: 
  									[(aMenu submorphs second isKindOf: MenuItemMorph) 
  										and: [aMenu submorphs second contents = 'dismiss this menu']]) 
  								ifTrue: 
  									[aMenu submorphs first delete.	"delete title"
  									aMenu submorphs first delete.	"delete stay-up item"
  									(aMenu submorphs first knownName = #line) 
  										ifTrue: [aMenu submorphs first delete]]].
  					toAdd removeAllMorphs.
  					toAdd addMorph: (appearanceMorph := m submorphs first).
  					appearanceMorph position: toAdd position.
  					appearanceMorph lock.
  					toAdd fitContents].
  			toAdd ifNil: [rejects add: m] ifNotNil: [tabsToUse add: toAdd]].
  	tabsToUse isEmpty 
  		ifTrue: [^self inform: 'Sorry, must have at least one tab'].
  	book newTabs: tabsToUse.
  	book tabsMorph color: pageHolder color.
  	oldTop := self topRendererOrSelf.	"in case some maniac has flexed the sorter"
  	oldOwner := oldTop owner.
  	oldTop delete.
  	oldOwner addMorphFront: book!



More information about the Squeak-dev mailing list