47ceb24897e8 — Gerald Klix (speedy) a month ago
SUM Manually copied the office roots package.
1 files changed, 239 insertions(+), 24 deletions(-)

M haver/office/OfficeRoots.pck.st
M haver/office/OfficeRoots.pck.st +239 -24
@@ 1,4 1,4 @@ 
-'From Haver7.0 [latest update: #6454] on 21 June 2024 at 3:58:15 pm'!
+'From Haver7.0 [latest update: #6454] on 26 June 2024 at 2:01:48 pm'!
 'Description I provide a (persistent) root for all the office data like:
 
 - ToDo items

          
@@ 6,12 6,12 @@ 
 - Documents
 
 and a lot more.'!
-!provides: 'OfficeRoots' 1 68!
+!provides: 'OfficeRoots' 1 70!
 !requires: 'IdGeneration' 1 2 nil!
+!requires: 'ActionBuilder' 1 36 nil!
 !requires: 'ActionButtons' 1 47 nil!
-!requires: 'ActionBuilder' 1 36 nil!
 !requires: 'States' 1 0 nil!
-!requires: 'PlanF' 1 24 nil!
+!requires: 'PlanF' 1 28 nil!
 !requires: 'SystemMorphs' 1 15 nil!
 SystemOrganization addCategory: #OfficeRoots!
 SystemOrganization addCategory: #'OfficeRoots-Items'!

          
@@ 27,8 27,8 @@ Modules newEnvironment: #OfficeRoots!
 
 !interfacesOf: OfficeRoots!
 Modules environment: #OfficeRoots ::
-	interface: #API exporting: #(#OfficeItemListMorph #OfficeItemWrapper #Roots) ::
-	interface: #SPI exporting: #(#OfficeItemListMorph #AbstractRoots #GroupingSubItemWrappersModel #SubItemWrappersModel #ConfigurationSwitchingGroupingSubItemWrappersModel #ListItemWrapper #SearchResultItemWrapper #OfficeItemWrapper) ::
+	interface: #API exporting: #(#OfficeItemListMorph #Roots #OfficeItemWrapper) ::
+	interface: #SPI exporting: #(#ListItemWrapper #SubItemWrappersModel #AbstractRoots #SearchResultItemWrapper #OfficeItemListMorph #GroupingSubItemWrappersModel #ConfigurationSwitchingGroupingSubItemWrappersModel #OfficeItemWrapper) ::
 	interface: #UTI exporting: #(#ListItemWrapper)!
 
 !importsOf: OfficeRoots!

          
@@ 62,6 62,28 @@ Modules environment: #OfficeRoots ::
 (Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) class
 	instanceVariableNames: ''!
 
+!classDefinition: (Modules>>#OfficeRoots>>#LinkingOfficeItem) category: #'OfficeRoots-Items'!
+(Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) subclass: #LinkingOfficeItem
+	instanceVariableNames: ''
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'OfficeRoots-Items'
+	inModule: #OfficeRoots!
+!classDefinition: (Modules>>#OfficeRoots>>#LinkingOfficeItem) class category: #'OfficeRoots-Items'!
+(Modules>>#OfficeRoots>>#LinkingOfficeItem) class
+	instanceVariableNames: ''!
+
+!classDefinition: (Modules>>#OfficeRoots>>#LinkContainersCollection) category: #'OfficeRoots-Items'!
+(Modules>>#OfficeRoots>>#AbstractOfficeItem) subclass: #LinkContainersCollection
+	instanceVariableNames: 'root'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'OfficeRoots-Items'
+	inModule: #OfficeRoots!
+!classDefinition: (Modules>>#OfficeRoots>>#LinkContainersCollection) class category: #'OfficeRoots-Items'!
+(Modules>>#OfficeRoots>>#LinkContainersCollection) class
+	instanceVariableNames: ''!
+
 !classDefinition: (Modules>>#OfficeRoots>>#SubItemWrappersConfiguration) category: #'OfficeRoots-Models'!
 (Modules>>#OfficeRoots>>#AbstractOfficeItem) subclass: #SubItemWrappersConfiguration
 	instanceVariableNames: 'category header description subItemsFilter subItemsSorter subItemsGrouper singleSubItemAdjuster subItemsCollectionAdjuster'

          
@@ 139,6 161,17 @@ Modules environment: #OfficeRoots ::
 (Modules>>#OfficeRoots>>#OfficeItemListMorph) class
 	instanceVariableNames: ''!
 
+!classDefinition: (Modules>>#OfficeRoots>>#IDEditingOfficeItemListMorph) category: #'OfficeRoots-Morphs'!
+(Modules>>#OfficeRoots>>#OfficeItemListMorph) subclass: #IDEditingOfficeItemListMorph
+	instanceVariableNames: ''
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'OfficeRoots-Morphs'
+	inModule: #OfficeRoots!
+!classDefinition: (Modules>>#OfficeRoots>>#IDEditingOfficeItemListMorph) class category: #'OfficeRoots-Morphs'!
+(Modules>>#OfficeRoots>>#IDEditingOfficeItemListMorph) class
+	instanceVariableNames: ''!
+
 !classDefinition: (Modules>>#OfficeRoots>>#ConfigurationSwitchingGroupingSubItemWrappersMorph) category: #'OfficeRoots-Morphs'!
 (Modules>>#SystemMorphs>>#AbstractSystemMorph) subclass: #ConfigurationSwitchingGroupingSubItemWrappersMorph
 	instanceVariableNames: 'isTopLevel subItemsWrappersSubModel selectionButton'

          
@@ 196,7 229,7 @@ Object subclass: #AbstractRoots
 
 !classDefinition: (Modules>>#OfficeRoots>>#Roots) category: #'OfficeRoots-Roots'!
 (Modules>>#OfficeRoots>>#AbstractRoots) subclass: #Roots
-	instanceVariableNames: 'todoItems addresses documents calendars spreadsheets workspaces worldStates portfolio'
+	instanceVariableNames: 'todoItems addresses documents calendars spreadsheets workspaces worldStates portfolio linkContainers'
 	classVariableNames: ''
 	poolDictionaries: ''
 	category: 'OfficeRoots-Roots'

          
@@ 212,6 245,13 @@ I am the abstract super class of all off
 !(Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) commentStamp: '<historical>' prior: 0!
 I am an office item that just links to its items, but does not own them, meaning it is not the parent of it's items.!
 
+!(Modules>>#OfficeRoots>>#LinkingOfficeItem) commentStamp: '<historical>' prior: 0!
+I am I generic collection of linking objects.!
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) commentStamp: '<historical>' prior: 0!
+I am a collection of link containers.
+Link containers are my default item class, but I am able to hold items of other classes.!
+
 !(Modules>>#OfficeRoots>>#SubItemWrappersConfiguration) commentStamp: '<historical>' prior: 0!
 I store one (simple) configuration for an instance of SubItemWrappersConfigurationModel.
 

          
@@ 471,14 511,13 @@ parent: aParent
 
 	^ self parent: aParent doneBy: nil! !
 
-!(Modules>>#OfficeRoots>>#AbstractOfficeItem) methodsFor: 'accessing' stamp: 'KLG 8/18/2023 16:11:40'!
+!(Modules>>#OfficeRoots>>#AbstractOfficeItem) methodsFor: 'accessing' stamp: 'KLG 6/25/2024 21:32:24'!
 parent: aParent doneBy: aRequestorOrNil
 	"Set my parent done by aRequestorOrNil."
 
 	self removeFromParent.
 	parentItem := aParent.
 	aParent privateAddItem: self doneBy: aRequestorOrNil.
-	self flagHaver: 'We might update the store and destroy it''s state while loading'.
 	self withStoreDo: [ :store |
 		store 
 			updateObject: self;

          
@@ 1427,11 1466,14 @@ wordDelimiters
 
 	^ ' .,;:!!?[]{}()«»“”"'''! !
 
-!(Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) methodsFor: 'accessing' stamp: 'KLG 3/28/2024 23:23:31'!
+!(Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) methodsFor: 'accessing' stamp: 'KLG 6/25/2024 21:35:08'!
 addItem: anItem doneBy: aRequestorOrNil
 	"Add anItem."
 
-	^ self privateAddItem: anItem doneBy: aRequestorOrNil! !
+	| answer |
+	answer :=  self privateAddItem: anItem doneBy: aRequestorOrNil.
+	self withStoreDo: [ :storeNotNil |		 storeNotNil updateObject: self ].
+	^ answer! !
 
 !(Modules>>#OfficeRoots>>#AbstractLinkingOfficeItem) methodsFor: 'accessing' stamp: 'KLG 3/28/2024 23:33:15'!
 itemAtId: anId

          
@@ 1526,6 1568,80 @@ itemsCollectionClass
 
 	^ OrderedCollection! !
 
+!(Modules>>#OfficeRoots>>#LinkingOfficeItem) class methodsFor: 'printing' stamp: 'KLG 6/25/2024 13:54:34'!
+printName
+	"Answer my name used in printing."
+
+	^ 'Links'! !
+
+!(Modules>>#OfficeRoots>>#LinkingOfficeItem) class methodsFor: 'instance creation' stamp: 'KLG 6/25/2024 14:04:17'!
+browserMorphClass
+	"Answer my browser morph."
+	
+	^ IDEditingOfficeItemListMorph! !
+
+!(Modules>>#OfficeRoots>>#LinkingOfficeItem) class methodsFor: 'persistence' stamp: 'KLG 6/25/2024 22:22:23'!
+recordDescriptionForPlanF: aStore
+	"Answer a record description for my instances."
+
+	^ aStore recordDescriptionClass
+		forClass: self
+		storeInstanceVariables: #(id)
+		gettersAndSetters: #(
+			(itemsForPlanF itemsFromPlanF:))! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) methodsFor: 'accessing' stamp: 'KLG 6/25/2024 20:47:55'!
+root
+	"Answer the value of root"
+
+	^ root! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) methodsFor: 'accessing' stamp: 'KLG 6/25/2024 13:48:12'!
+root: aRoots 
+	"Set the root object."
+
+	root := aRoots! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) methodsFor: 'testing' stamp: 'KLG 6/25/2024 20:49:13'!
+canSave
+	"Answer true if we can save our self."
+
+	^ root notNil! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) methodsFor: 'persistence' stamp: 'KLG 6/25/2024 20:52:56'!
+withStoreDo: aBlock
+	"Evaluate aBock with my store."
+
+	^ root ifNotNil: [ root withStoreDo: aBlock ]! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) class methodsFor: 'instance creation' stamp: 'KLG 6/25/2024 13:32:31'!
+browserMorphClass
+	"Answer my browser morph."
+	
+	^ OfficeItemListMorph! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) class methodsFor: 'instance creation' stamp: 'KLG 6/25/2024 12:07:02'!
+itemClass
+	"Answer my items class."
+	
+	^ LinkingOfficeItem! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) class methodsFor: 'persistence' stamp: 'KLG 6/25/2024 22:23:04'!
+recordDescriptionForPlanF: aStore
+	"Answer a record description for my instances."
+
+	^ aStore recordDescriptionClass
+		forClass: self
+		storeInstanceVariables: #(id)
+		gettersAndSetters: #(
+			(itemsForPlanF itemsFromPlanF:))! !
+
+!(Modules>>#OfficeRoots>>#LinkContainersCollection) class methodsFor: 'printing' stamp: 'KLG 6/25/2024 13:54:25'!
+printName
+	"Answer my name used in printing."
+
+	^ 'LinkContainers'! !
+
 !(Modules>>#OfficeRoots>>#SubItemWrappersConfiguration) methodsFor: 'accessing' stamp: 'KLG 4/29/2024 19:48:09'!
 configureSubItemsWrapperModel: aModel
 	"Configure a model."

          
@@ 2278,6 2394,12 @@ officeItemsMenu
 
 	^ self menuBuilder buildUIElement! !
 
+!(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/25/2024 13:58:49'!
+addDetailMorphsTo: aLayoutMorph
+	"Add morphs for editing simple details.
+	
+	Do nothing here, but implement in subclasses."! !
+
 !(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 4/26/2024 12:46:35'!
 buildActions
 	"Build all my actions."

          
@@ 2338,7 2460,7 @@ buildActions
 							enabledSelector: #someoneCanSave					] ] ].
 	^ builder! !
 
-!(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 4/26/2024 12:50:11'!
+!(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/25/2024 14:00:02'!
 buildMorphicWidget
 	"Build the widget."
 

          
@@ 2346,7 2468,8 @@ buildMorphicWidget
 	self beRow.
 	(buttonsMorph := self buttonsBuilder buildUIElement)
 		color: `Color black`.
-	(itemsPane := LayoutMorph newColumn)
+	self addDetailMorphsTo: 	(itemsPane := LayoutMorph newColumn).
+	itemsPane
 		addMorph: self newSearchPane fixedHeight: 30;
 		addAdjusterMorph;
 		addMorphUseAll: self newItemsList.

          
@@ 2360,7 2483,7 @@ buttonsBuilder
 
 	^ self menuBuilder buttonsBuilder! !
 
-!(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 4/26/2024 11:51:32'!
+!(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/25/2024 14:10:57'!
 newItemsList
 	"Answer a new items list morph."
 

          
@@ 2375,7 2498,7 @@ newItemsList
 		dropAction: #dropItemWrapper:
 		dropChecker: #acceptsItemWrapper: ::
 			doubleClickSelector: #browseSelectedItem;
-			autoExpand: true.! !
+			autoExpand: false.! !
 
 !(Modules>>#OfficeRoots>>#OfficeItemListMorph) methodsFor: 'commands' stamp: 'KLG 4/25/2024 21:57:58'!
 completeRemovalConfirmed

          
@@ 2412,6 2535,18 @@ officeItemsKeystroke: aUnicodeCodePoint
 			[ $a ] -> [ self subItemsWrappersSubModel addItemToSelectedItem ] }
 		otherwise: [ self flash ]! !
 
+!(Modules>>#OfficeRoots>>#IDEditingOfficeItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/25/2024 14:05:55'!
+addDetailMorphsTo: aLayoutMorph
+	"Add morphs for editing simple details."
+	
+	aLayoutMorph
+		addMorph: (TextModelMorph
+			textProvider: self model
+			textGetter: #idForUI
+			textSetter: #idFromUI: ::
+				acceptOnCR: true)
+		fixedHeight: 30! !
+
 !(Modules>>#OfficeRoots>>#ConfigurationSwitchingGroupingSubItemWrappersMorph) methodsFor: 'GUI building' stamp: 'KLG 4/30/2024 18:01:06'!
 buildMorphicWidget 
 	"Builder my widget."

          
@@ 2856,6 2991,19 @@ documents: anObject
 			updateObject: documents;
 			flush ]! !
 
+!(Modules>>#OfficeRoots>>#Roots) methodsFor: 'accessing' stamp: 'KLG 6/25/2024 19:18:32'!
+linkContainers
+	"Answer a collection of link containers."
+
+	linkContainers ifNil: [
+		(linkContainers := self linkContainersCollectionClass new) root: self..
+		self withStoreDo: [ :storeNonNil |
+			storeNonNil
+				updateObject: self;
+				flush ] ].
+	linkContainers root: self. ": This instance variable is not persistent!!"
+	^ linkContainers! !
+
 !(Modules>>#OfficeRoots>>#Roots) methodsFor: 'accessing' stamp: 'KLG 12/15/2023 15:34:29'!
 portfolio
 	"Answer the value of investments"

          
@@ 2997,6 3145,12 @@ hasInvestments
 
 	^ portfolio notNil! !
 
+!(Modules>>#OfficeRoots>>#Roots) methodsFor: 'testing' stamp: 'KLG 6/25/2024 13:36:57'!
+hasLinkContainers
+	"Answer true if we have link containers."
+
+	^ linkContainers notNil! !
+
 !(Modules>>#OfficeRoots>>#Roots) methodsFor: 'testing' stamp: 'KLG 8/18/2023 21:49:01'!
 hasSpreadsheets
 	"Answer true if we have spread sheets."

          
@@ 3040,6 3194,12 @@ investingFeatureRequirement
 
 	^ self class investingFeatureRequirement! !
 
+!(Modules>>#OfficeRoots>>#Roots) methodsFor: 'instance creation' stamp: 'KLG 6/25/2024 12:02:39'!
+linkContainersCollectionClass
+	"Answer the class of that holds link containers."
+
+	^ self class linkContainersCollectionClass! !
+
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'persistence' stamp: 'KLG 12/6/2023 10:46:21'!
 defaultStoreName
 	"Answer the default store name."

          
@@ 3049,13 3209,13 @@ defaultStoreName
 		self iteration printOn: stream base: 36.
 		stream nextPutAll: '.planF' ]! !
 
-!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'persistence' stamp: 'KLG 12/14/2023 19:07:57'!
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'persistence' stamp: 'KLG 6/25/2024 11:55:48'!
 recordDescriptionForPlanF: aStore
 	"Answer a record description for my instances."
 
 	^ aStore recordDescriptionClass
 		forClass: self
-		storeInstanceVariables: #(todoItems addresses documents calendars spreadsheets workspaces worldStates portfolio)! !
+		storeInstanceVariables: #(todoItems addresses documents calendars spreadsheets workspaces worldStates portfolio linkContainers)! !
 
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'interations' stamp: 'KLG 12/6/2023 10:49:42'!
 iteration

          
@@ 3074,12 3234,24 @@ initialize
 
 	Smalltalk addToShutDownList: self! !
 
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'instance creation' stamp: 'KLG 6/25/2024 13:44:50'!
+linkContainersCollectionClass
+	"Answer the class of that holds link containers."
+
+	^ LinkContainersCollection! !
+
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 9/12/2023 22:23:00'!
 browseDocuments
 	"Browse the persitent document /list."
 	
 	self default documents secondaryBrowse! !
 
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 6/25/2024 13:44:31'!
+browseLinkContainers
+	"Browse the link containers sheets."
+	
+	^ self default linkContainers browse! !
+
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 12/14/2023 11:46:20'!
 browsePortfolio
 	"Browse the persitent portfolio."

          
@@ 3092,11 3264,13 @@ browseSpreadSheets
 	
 	^ self default spreadsheets browse! !
 
-!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 8/23/2023 11:35:59'!
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 6/26/2024 13:53:21'!
 browseToDo
 	"Browse the persitent todo item/list."
 	
-	self default todoItems secondaryBrowse! !
+	self default todoItems hasItems
+		ifTrue: [ self default		 todoItems secondaryBrowse ]
+		ifFalse: [ self default todoItems browse ]! !
 
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 8/23/2023 13:26:22'!
 browseWorkspaces

          
@@ 3122,6 3296,12 @@ newNote
 		on: newItem
 ! !
 
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 6/25/2024 13:53:41'!
+openLinkContainer
+	"Create an open a new link container."
+
+	^ self default linkContainers addItem browse! !
+
 !(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'browsing' stamp: 'KLG 8/23/2023 20:17:36'!
 openWorkspace
 	"Create an open a new workspace."

          
@@ 3134,7 3314,7 @@ openWorldstate
 
 	^ self default worldStates addItem browse! !
 
-!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'menu-world' stamp: 'KLG 12/15/2023 15:48:08'!
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'menu-world' stamp: 'KLG 6/26/2024 13:32:11'!
 openPersistentToolsMenu
 	"Open our menu with the persistent tools."
 	

          
@@ 3147,19 3327,19 @@ openPersistentToolsMenu
 	menu
 		add: 'New Note' action: #newNote icon: #textEditorIcon ::
 			setBalloonText: `'Add a simple ', 'note' bold, ' to the ToDo list and open it'`.
-	menu
+	"F: menu
 		addLine;
 		add: 'Documents' action: #browseDocuments icon: #genericTextIcon ::
-			setBalloonText: `'Open Haver''s list of persistent ', 'Documents' bold`.
+			setBalloonText: `'Open Haver''s list of persistent ', 'Documents' bold`."
 	menu
 		addLine;
 		add: 'Spread Sheets' action: #browseSpreadSheets icon: #spreadsheetIcon ::
 			setBalloonText: `'Open Haver''s list of persistent ', 'Spread Sheets' bold`.
-	self investingFeatureRequirement ifNotNil: [
+	"F:self investingFeatureRequirement ifNotNil: [
 		menu
 			addLine;
 			add: 'Portfolio' action: #browsePortfolio icon: #spreadsheetIcon ::
-				setBalloonText: `'Open Haver''s persistent ', 'Portfolio' bold` ].
+				setBalloonText: `'Open Haver''s persistent ', 'Portfolio' bold` ]."
 	menu
 		addLine;
 		add: 'Workspaces' action: #browseWorkspaces icon: #systemIcon ::

          
@@ 3176,6 3356,19 @@ openPersistentToolsMenu
 			setBalloonText: `'Add a ', 'world state' bold, ' to the list of world states and open it'`.
 	menu
 		addLine;
+		add: 'Link Containers' action: #browseLinkContainers icon: #refreshIcon ::
+			setBalloonText: `'Open Haver''s list of persistent ', 'link containers' bold`.
+	menu
+		add: 'New Link Container' action: #openLinkContainer icon: #halfRefreshIcon ::
+			setBalloonText: `'Add a ', 'link container' bold, ' to the link container collection list and open it'`.
+	menu
+		addLine;
+		addUpdating: 'Zap' action: #closeAllAndZapDefaults" icon: #closeIcon" ::
+			setIcon: #closeIcon ::
+			setBalloonText: `'Reset the ', 'default root object' bold, ' to to reload everything\\Also close all related windows.' withNewLines`::
+			isEnabled: [ defaultInstance notNil ].
+	menu
+		addLine;
 		add: 'Document Id'
 			target: IdGenerator
 			action: #copyNextDocumentIdToClipboardAndShowIt

          
@@ 3212,4 3405,26 @@ investingFeatureRequirement
 	(answer := FeatureRequirement name: 'Investing') findPackageFileAsReqOf: nil ::
 		ifFalse: [ ^nil ].
 	^ answer! !
+
+!(Modules>>#OfficeRoots>>#Roots) class methodsFor: 'user interface support' stamp: 'KLG 6/26/2024 13:38:28'!
+closeAllAndZapDefaults
+	"Close all windows with model instances of AbstractOfficeItem subclasses and
+	then zap the root object.
+	
+	This action should force e reaload from the database,
+	when windows are repopend."
+	
+	defaultInstance ifNil: [ ^self ].
+	self 
+		confirm:
+			'Do you realy want to close all office item related windows and zap the default root object?' ::
+				ifFalse: [ ^ self ].
+	UISupervisor runningWorld ifNotNil: [ :rw |
+		SystemWindow
+			windowsIn: rw
+			satisfying: [ :window | window model isKindOf: AbstractOfficeItem ] :: do: [: window |
+				window dismissMorph ] ].
+	Modules hasEnvironment: #NuMach :: ifTrue: [
+		Modules >> #NuMach >> #PersistentTodoItem :: zapDefault ].
+	self zapDefault! !
 (Modules>>#OfficeRoots>>#Roots) initialize!