a37d95c81812 — Gerald Klix (speedy) 3 months ago
SUM: Removed auto expand in tree views.
1 files changed, 229 insertions(+), 229 deletions(-)

M haver/office/NuMach.pck.st
M haver/office/NuMach.pck.st +229 -229
@@ 1,14 1,14 @@ 
-'From Haver7.0 [latest update: #6454] on 21 June 2024 at 3:58:24 pm'!
+'From Haver7.0 [latest update: #6454] on 25 June 2024 at 6:57:31 pm'!
 'Description NuMach is a very simple to list.
 
 Hopefully it will serve as a base for something more elaborate.'!
-!provides: 'NuMach' 1 88!
+!provides: 'NuMach' 1 89!
 !requires: 'ActionBuilder' 1 35 nil!
+!requires: 'OfficeRoots' 1 68 nil!
 !requires: 'FacetsMorphs' 1 4 nil!
 !requires: 'Tracing' 1 13 nil!
 !requires: 'PlanF' 1 25 nil!
 !requires: 'SystemMorphs' 1 15 nil!
-!requires: 'OfficeRoots' 1 68 nil!
 !requires: 'Cuis-Base' 60 5981 nil!
 !requires: 'IdGeneration' 1 1 nil!
 !requires: 'ActionButtons' 1 33 nil!

          
@@ 38,13 38,24 @@ Modules environment: #NuMach ::
 	import: #(#TranscriptTracer) from: #API of: Modules>>#Tracing :: 
 	import: #(#TargetButton #TargetToggleButton) from: #API of: Modules>>#ActionButtons :: 
 	import: #(#ActionBuilder) from: #API of: Modules>>#ActionBuilder :: 
+	import: #(#OfficeItemWrapper) from: #API of: Modules>>#OfficeRoots :: 
 	import: #(#DetailsMorph) from: #API of: Modules>>#FacetsMorphs :: 
-	import: #(#OfficeItemWrapper) from: #API of: Modules>>#OfficeRoots :: 
 	import: #(#Store) from: #API of: Modules>>#PlanF :: 
 	import: #API of: Modules>>#SystemMorphs :: 
 	import: #(#GermanDateAndTimeInputMorph) from: #API of: Modules>>#ValueEditors :: 
 	import: #(#IdGenerator) from: #API of: Modules>>#IdGeneration!
 
+!classDefinition: (Modules>>#NuMach>>#Alarm) category: #'NuMach-Timing'!
+(Modules>>#ValueEditors>>#SimpleDateAndTimeModel) subclass: #Alarm
+	instanceVariableNames: 'item alarmProcess'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'NuMach-Timing'
+	inModule: #NuMach!
+!classDefinition: (Modules>>#NuMach>>#Alarm) class category: #'NuMach-Timing'!
+(Modules>>#NuMach>>#Alarm) class
+	instanceVariableNames: ''!
+
 !classDefinition: (Modules>>#NuMach>>#TodoItem) category: #'NuMach-Items'!
 (Modules>>#OfficeRoots>>#AbstractOfficeItem) subclass: #TodoItem
 	instanceVariableNames: 'header description state timing'

          
@@ 287,17 298,6 @@ Modules environment: #NuMach ::
 (Modules>>#NuMach>>#Template) class
 	instanceVariableNames: ''!
 
-!classDefinition: (Modules>>#NuMach>>#Alarm) category: #'NuMach-Timing'!
-(Modules>>#ValueEditors>>#SimpleDateAndTimeModel) subclass: #Alarm
-	instanceVariableNames: 'item alarmProcess'
-	classVariableNames: ''
-	poolDictionaries: ''
-	category: 'NuMach-Timing'
-	inModule: #NuMach!
-!classDefinition: (Modules>>#NuMach>>#Alarm) class category: #'NuMach-Timing'!
-(Modules>>#NuMach>>#Alarm) class
-	instanceVariableNames: ''!
-
 !classDefinition: (Modules>>#NuMach>>#AbstractItemMorph) category: #'NuMach-Morphs'!
 (Modules>>#OfficeRoots>>#AbstractOfficeItemMorph) subclass: #AbstractItemMorph
 	instanceVariableNames: ''

          
@@ 486,6 486,9 @@ Object subclass: #AbstractMemento
 	instanceVariableNames: ''!
 
 
+!(Modules>>#NuMach>>#Alarm) commentStamp: '<historical>' prior: 0!
+I am an alarm.!
+
 !(Modules>>#NuMach>>#TodoItem) commentStamp: '<historical>' prior: 0!
 I am a item in a todo list and a todolist on one class.!
 

          
@@ 538,9 541,6 @@ I am a research task.!
 !(Modules>>#NuMach>>#Template) commentStamp: '<historical>' prior: 0!
 I am a template for other items.!
 
-!(Modules>>#NuMach>>#Alarm) commentStamp: '<historical>' prior: 0!
-I am an alarm.!
-
 !(Modules>>#NuMach>>#AbstractItemMorph) commentStamp: '<historical>' prior: 0!
 I am the abstract super class of all todo item morphs.!
 

          
@@ 595,27 595,6 @@ I am version three of NuMach's memento c
 Currently the only timing information we have is an alarm.
 which we store as DateAndTime.!
 
-!(Modules>>#NuMach>>#TodoItem) methodsFor: 'printing' stamp: 'KLG 5/30/2023 13:19:05'!
-printOn: aStream
-	"Print me on a stream"
-
-	aStream
-		nextPutAll: self printName;
-		nextPut: $(;
-		print: self identityHash;
-		nextPut: $);
-		nextPut: $[;
-		nextPutAll: self id;
-		nextPut: $]! !
-
-!(Modules>>#NuMach>>#PersistentTodoItem) class methodsFor: 'system startup' stamp: 'KLG 8/15/2023 14:57:42'!
-startUp: isRealStartup
-	"Will be sent on start up."
-
-	isRealStartup ifTrue: [
-		defaultInstance ifNotNil: [
-			defaultInstance scheduleAlarms ] ]! !
-
 !(Modules>>#NuMach>>#Alarm) class methodsFor: 'system startup' stamp: 'KLG 1/6/2024 17:06:35'!
 shutDown: isRealShutdown
 	"Will be sent on start up."

          
@@ 642,6 621,27 @@ printOn: aStream
 			print: alarmProcess ].
 	aStream nextPut: $]	! !
 
+!(Modules>>#NuMach>>#TodoItem) methodsFor: 'printing' stamp: 'KLG 5/30/2023 13:19:05'!
+printOn: aStream
+	"Print me on a stream"
+
+	aStream
+		nextPutAll: self printName;
+		nextPut: $(;
+		print: self identityHash;
+		nextPut: $);
+		nextPut: $[;
+		nextPutAll: self id;
+		nextPut: $]! !
+
+!(Modules>>#NuMach>>#PersistentTodoItem) class methodsFor: 'system startup' stamp: 'KLG 8/15/2023 14:57:42'!
+startUp: isRealStartup
+	"Will be sent on start up."
+
+	isRealStartup ifTrue: [
+		defaultInstance ifNotNil: [
+			defaultInstance scheduleAlarms ] ]! !
+
 !(Modules>>#NuMach>>#AbstractItemState) methodsFor: 'printing' stamp: 'KLG 7/20/2023 11:47:26'!
 printOn: aStream
 	"Print a nice represantion on aStream."

          
@@ 663,6 663,193 @@ printOn: aStream
 					nextPut: $] ] ]
 		ifNil: [ aStream nextPutAll: 'State' ]! !
 
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 8/11/2023 13:01:32'!
+dateAndTime: aDateAndTime
+	"Set date and time."
+
+	super dateAndTime: aDateAndTime.
+	self scheduleAlarm.
+	item ifNotNil: [
+		item withStoreDo: [ :store |
+			store
+				updateObject: self;
+				flush ] ]! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 7/3/2023 15:20:53'!
+item
+	"Answer the value of item"
+
+	^ item! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 7/8/2023 13:42:05'!
+item: anObject
+	"Set the value of item"
+
+	(item := anObject)
+		ifNil: [ self killAlarm ]
+		ifNotNil: [ self scheduleAlarm ]! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'initialization' stamp: 'KLG 7/7/2023 00:02:47'!
+initialValue
+	"Answer my initial value."
+
+	| now answer |
+	(now := DateAndTime now) dayMonthYearDo: [ :d :m :y |
+		answer := DateAndTime 
+			year: y
+			month: m
+			day: d
+			hour: (now hour + 1 max: 8)
+			minute: 0.
+		answer time > (Time hour: 22 minute: 0 second: 0)
+			ifTrue: [
+				answer :=
+					DateAndTime 
+						year: y
+						month: m
+						day: d + 1
+						hour: 8
+						minute: 0 ] ].
+	^ answer! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'user interface support' stamp: 'KLG 7/8/2023 22:18:46'!
+alarmDueAlertColor
+	"Answer the color for alarm due events."
+
+	^ self dateAndTime < DateAndTime now ifTrue: [ `Color cyan` ]! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'persistence' stamp: 'KLG 7/7/2023 20:38:32'!
+memento
+	"Answer a memento for me."
+
+	| answer |
+	answer := self class new.
+	answer dateAndTime: self dateAndTime.
+	^ answer! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:32:16'!
+alarm
+	"Show an alarm for this item."
+
+	self
+		changed: #alarmDueAlertColor;
+		confirm: (String streamContents: [ :stream |
+			stream
+				nextPutAll: self class displayString;
+				nextPutAll: ' for Item ''';
+				nextPutAll: item header;
+				nextPut: $';
+				nextPut: `Character newLineCharacter`;
+				nextPutAll: 'Browse the item?'])
+		orCancel: [
+			^ self postPoneAlarm ] :: ifTrue: [
+			item browse ]! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/7/2023 16:03:36'!
+alarmDateAndTime
+	"Answer our alarm time."
+
+	^ self dateAndTime! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/8/2023 13:41:46'!
+killAlarm
+	"Kill my alarms if any."
+
+	alarmProcess ifNotNil: [
+		alarmProcess terminate.
+		alarmProcess := nil ]! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:33:58'!
+postPoneAlarm
+	"Post pone me for 2 minutes."
+	
+	self postPoneAlarmFor: 2 minutes! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:33:58'!
+postPoneAlarmFor: aDuration
+	"Postpone me by a duration."
+
+	self dateAndTime: DateAndTime now + aDuration! !
+
+!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 8/4/2023 14:14:15'!
+scheduleAlarm
+	"Add an alarm for me."
+
+	| now |
+	self killAlarm.
+	item ifNil: [ ^ self ].
+	self changed: #alarmDueAlertColor.
+	self class shouldScheduleAlarm ifFalse: [ ^ self ].
+	self dateAndTime > (now := DateAndTime now) ifTrue: [ | delay |
+		delay := Delay forDuration: self dateAndTime - now.
+		(alarmProcess := [
+			delay wait. 
+			UISupervisor whenUIinSafeState: [ self alarm ] ] newProcess)
+				priority: Processor lowIOPriority;
+				name: self dateAndTime printString, ': Alarming for ''', self item header, '''';
+				resume ]
+			! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'instance creation' stamp: 'KLG 7/5/2023 11:52:25'!
+browserMorphClass
+	"Answer the toplevel morph class for this model."
+
+	^ GermanDateAndTimeInputMorph! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'instance creation' stamp: 'KLG 7/5/2023 11:33:24'!
+forItem: anItem
+	"Create an instance of mine for an item."
+
+	^ self new
+		item: anItem;
+		yourself! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'persistence' stamp: 'KLG 8/3/2023 18:55:51'!
+recordDescriptionForPlanF: aStore
+	"Answer a record description for my instances."
+
+	^ aStore recordDescriptionClass
+		forClass: self
+		storeInstanceVariables: #(dateAndTime)! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'scheduling' stamp: 'KLG 8/15/2023 14:42:18'!
+killAllAlarms
+	"Kill all my alarms."
+
+	^ self allInstancesDo: [ :alarm |
+		TodoItem inDebugMode ifTrue: [
+			Transcript
+				newLine;
+				show: 'About to kill: ';
+				show: alarm ].
+		alarm killAlarm ]! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'user interface' stamp: 'KLG 7/5/2023 11:32:04'!
+balloonText
+	"Answer a text to be displayed by the UI as a balloon help text."
+
+	^ self displayString! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'user interface' stamp: 'KLG 7/5/2023 11:32:14'!
+displayString
+	"Answer a text to be displayed by the UI e.g. menus."
+
+	^ self name asString! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'class initialization' stamp: 'KLG 8/15/2023 14:43:00'!
+initialize
+	"Initialize me by adding me to the shutdown list."
+
+	Smalltalk addToShutDownList: self! !
+
+!(Modules>>#NuMach>>#Alarm) class methodsFor: 'debugging' stamp: 'KLG 8/4/2023 17:22:26'!
+shouldScheduleAlarm
+	"Answer true if we should schedule alarms.
+	
+	Can be used for debugging purposes."
+
+	^ TodoItem inDebugMode not! !
+
 !(Modules>>#NuMach>>#TodoItem) methodsFor: 'printing' stamp: 'KLG 7/16/2023 15:32:22'!
 editPrintText
 	"Answer my print text."

          
@@ 1615,193 1802,6 @@ itemClass
 	
 	^ self! !
 
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 8/11/2023 13:01:32'!
-dateAndTime: aDateAndTime
-	"Set date and time."
-
-	super dateAndTime: aDateAndTime.
-	self scheduleAlarm.
-	item ifNotNil: [
-		item withStoreDo: [ :store |
-			store
-				updateObject: self;
-				flush ] ]! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 7/3/2023 15:20:53'!
-item
-	"Answer the value of item"
-
-	^ item! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'accessing' stamp: 'KLG 7/8/2023 13:42:05'!
-item: anObject
-	"Set the value of item"
-
-	(item := anObject)
-		ifNil: [ self killAlarm ]
-		ifNotNil: [ self scheduleAlarm ]! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'initialization' stamp: 'KLG 7/7/2023 00:02:47'!
-initialValue
-	"Answer my initial value."
-
-	| now answer |
-	(now := DateAndTime now) dayMonthYearDo: [ :d :m :y |
-		answer := DateAndTime 
-			year: y
-			month: m
-			day: d
-			hour: (now hour + 1 max: 8)
-			minute: 0.
-		answer time > (Time hour: 22 minute: 0 second: 0)
-			ifTrue: [
-				answer :=
-					DateAndTime 
-						year: y
-						month: m
-						day: d + 1
-						hour: 8
-						minute: 0 ] ].
-	^ answer! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'user interface support' stamp: 'KLG 7/8/2023 22:18:46'!
-alarmDueAlertColor
-	"Answer the color for alarm due events."
-
-	^ self dateAndTime < DateAndTime now ifTrue: [ `Color cyan` ]! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'persistence' stamp: 'KLG 7/7/2023 20:38:32'!
-memento
-	"Answer a memento for me."
-
-	| answer |
-	answer := self class new.
-	answer dateAndTime: self dateAndTime.
-	^ answer! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:32:16'!
-alarm
-	"Show an alarm for this item."
-
-	self
-		changed: #alarmDueAlertColor;
-		confirm: (String streamContents: [ :stream |
-			stream
-				nextPutAll: self class displayString;
-				nextPutAll: ' for Item ''';
-				nextPutAll: item header;
-				nextPut: $';
-				nextPut: `Character newLineCharacter`;
-				nextPutAll: 'Browse the item?'])
-		orCancel: [
-			^ self postPoneAlarm ] :: ifTrue: [
-			item browse ]! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/7/2023 16:03:36'!
-alarmDateAndTime
-	"Answer our alarm time."
-
-	^ self dateAndTime! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/8/2023 13:41:46'!
-killAlarm
-	"Kill my alarms if any."
-
-	alarmProcess ifNotNil: [
-		alarmProcess terminate.
-		alarmProcess := nil ]! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:33:58'!
-postPoneAlarm
-	"Post pone me for 2 minutes."
-	
-	self postPoneAlarmFor: 2 minutes! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 7/10/2023 16:33:58'!
-postPoneAlarmFor: aDuration
-	"Postpone me by a duration."
-
-	self dateAndTime: DateAndTime now + aDuration! !
-
-!(Modules>>#NuMach>>#Alarm) methodsFor: 'scheduling' stamp: 'KLG 8/4/2023 14:14:15'!
-scheduleAlarm
-	"Add an alarm for me."
-
-	| now |
-	self killAlarm.
-	item ifNil: [ ^ self ].
-	self changed: #alarmDueAlertColor.
-	self class shouldScheduleAlarm ifFalse: [ ^ self ].
-	self dateAndTime > (now := DateAndTime now) ifTrue: [ | delay |
-		delay := Delay forDuration: self dateAndTime - now.
-		(alarmProcess := [
-			delay wait. 
-			UISupervisor whenUIinSafeState: [ self alarm ] ] newProcess)
-				priority: Processor lowIOPriority;
-				name: self dateAndTime printString, ': Alarming for ''', self item header, '''';
-				resume ]
-			! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'instance creation' stamp: 'KLG 7/5/2023 11:52:25'!
-browserMorphClass
-	"Answer the toplevel morph class for this model."
-
-	^ GermanDateAndTimeInputMorph! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'instance creation' stamp: 'KLG 7/5/2023 11:33:24'!
-forItem: anItem
-	"Create an instance of mine for an item."
-
-	^ self new
-		item: anItem;
-		yourself! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'persistence' stamp: 'KLG 8/3/2023 18:55:51'!
-recordDescriptionForPlanF: aStore
-	"Answer a record description for my instances."
-
-	^ aStore recordDescriptionClass
-		forClass: self
-		storeInstanceVariables: #(dateAndTime)! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'scheduling' stamp: 'KLG 8/15/2023 14:42:18'!
-killAllAlarms
-	"Kill all my alarms."
-
-	^ self allInstancesDo: [ :alarm |
-		TodoItem inDebugMode ifTrue: [
-			Transcript
-				newLine;
-				show: 'About to kill: ';
-				show: alarm ].
-		alarm killAlarm ]! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'user interface' stamp: 'KLG 7/5/2023 11:32:04'!
-balloonText
-	"Answer a text to be displayed by the UI as a balloon help text."
-
-	^ self displayString! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'user interface' stamp: 'KLG 7/5/2023 11:32:14'!
-displayString
-	"Answer a text to be displayed by the UI e.g. menus."
-
-	^ self name asString! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'class initialization' stamp: 'KLG 8/15/2023 14:43:00'!
-initialize
-	"Initialize me by adding me to the shutdown list."
-
-	Smalltalk addToShutDownList: self! !
-
-!(Modules>>#NuMach>>#Alarm) class methodsFor: 'debugging' stamp: 'KLG 8/4/2023 17:22:26'!
-shouldScheduleAlarm
-	"Answer true if we should schedule alarms.
-	
-	Can be used for debugging purposes."
-
-	^ TodoItem inDebugMode not! !
-
 !(Modules>>#NuMach>>#AbstractItemMorph) methodsFor: 'submorphs-add/remove' stamp: 'KLG 6/3/2023 14:57:05'!
 addTodoItemMorph: anItemMorph
 	"Add a todo item morph to me."

          
@@ 2011,7 2011,7 @@ buildActions
 							enabledSelector: #someoneCanSave					] ] ].
 	^ builder! !
 
-!(Modules>>#NuMach>>#TodoItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/21/2024 15:48:35'!
+!(Modules>>#NuMach>>#TodoItemListMorph) methodsFor: 'GUI building' stamp: 'KLG 6/25/2024 11:48:50'!
 buildMorphicWidget
 	"Build the widget."
 

          
@@ 2030,7 2030,7 @@ buildMorphicWidget
 		dropAction: #dropItemWrapper:
 		dropChecker: #acceptsItemWrapper:)
 			doubleClickSelector: #browseSelectedItem;
-			autoExpand: true.
+			autoExpand: false.
 	(todoItemsPane := LayoutMorph newColumn)
 		addMorph: self newSearchPane fixedHeight: 30;
 		addAdjusterMorph;

          
@@ 3712,5 3712,5 @@ timing: anObject
 	"Set the value of timing"
 
 	timing := anObject! !
+(Modules>>#NuMach>>#Alarm) initialize!
 (Modules>>#NuMach>>#PersistentTodoItem) initialize!
-(Modules>>#NuMach>>#Alarm) initialize!