'From Squeak6.1alpha of 17 May 2024 [latest update: #23043] on 14 February 2025 at 9:04:43 pm'! TalkDataView subclass: #TalkInbox instanceVariableNames: 'mailingList projects nabbleNodeId subjectPrefix downloadRange messagePlaceholders conversationsPerContributions messagesPerContributions messagesPerIds lastRefreshed' classVariableNames: 'EnableSemanticSearch MessageSignature SendHtmlMessages' poolDictionaries: '' category: 'SqueakInboxTalk-Core'! !TalkInbox commentStamp: 'ct 7/24/2021 02:52' prior: 0! I am an inbox, the central artifact that SqueakInboxTalk involves. I provide unified access to the different kinds of artifacts that are relevant of the inbox-based development workflow for Squeak projects, i.e., conversations and contributions. Conversations are retrieved from the MailingLists package as original mail artifacts and represented as TalkConversation and TalkMessage instances in this package. Contributions are currently retrieved from Monticello only and are represented as TalkContribution subinstances. Unlike intended by my superclass, my state is not only bipartite but tripartite, so between key fields and cache fields, I also include some configurational fields. This object design is probably not the optimally suited until all eternity and might be extracted into a separate configuratino class in future. My current trichotomy is also handled specially in my class side's #clearAllCaches method. My most important accessors are #projects, #messages, and #conversations. My mails can be updated via #refreshMessages. I also provide some additional functionalities such as creating reply e-mails to messages and generating URLs to look up my messages and conversations in online archives of my mailing list. Visit the GitHub project for further information: ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 7/7/2021 22:19'! allPackageNames ^ ((self projects collect: #repositoryGroup) gather: #allPackageNames) as: Set! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 5/8/2021 16:19'! contributions ^ (self conversations gather: #contributions) as: Set! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 5/20/2021 18:54'! conversations ^ self mailingList conversations collect: [:mailConversation | TalkConversation on: mailConversation]! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 5/26/2021 16:43'! mailAddress ^ self mailingList mailAddress! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 8/26/2023 00:55'! messageForId: id ^ self messagesPerIds at: id ifAbsentPut: [(messagePlaceholders ifNil: [messagePlaceholders := WeakValueDictionary new]) at: id ifAbsentPut: (TalkMessagePlaceholder inbox: self messageId: id)]! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 7/7/2021 22:04'! messages ^ self conversations gather: #messages! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 5/20/2021 20:41'! mostRecentConversations ^ (self conversations talkSortedByHeavy: #latestDate) reversed "sorted: #latestDate descending optimized (~900% faster)"! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 5/7/2021 15:22'! name ^ self mailingList name! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 7/1/2023 19:24'! subjectPrefix ^ subjectPrefix ifNil: ['[{1}]' format: {self name}]! ! !TalkInbox methodsFor: 'accessing' stamp: 'ct 7/1/2023 14:47'! subjectPrefix: aStringOrNil subjectPrefix := aStringOrNil.! ! !TalkInbox methodsFor: '*SqueakInboxTalk-UI-browsing' stamp: 'ct 5/20/2021 18:58'! browse ^ TalkInboxBrowser openOn: self! ! !TalkInbox methodsFor: 'accessing - caches' stamp: 'ct 5/19/2021 20:51'! conversationsForContribution: aContribution ^ self conversationsPerContributions at: aContribution! ! !TalkInbox methodsFor: 'accessing - caches' stamp: 'ct 5/19/2021 22:01'! conversationsPerContributions "Cached." ^ conversationsPerContributions ifNil: [ | dictionary | dictionary := Dictionary new. self conversations do: [:conversation | conversation contributions do: [:contribution | (dictionary at: contribution ifAbsentPut: [Set new]) add: conversation]]. conversationsPerContributions := dictionary]! ! !TalkInbox methodsFor: 'accessing - caches' stamp: 'ct 6/29/2021 15:23'! messagesForContribution: aContribution ^ self messagesPerContributions at: aContribution! ! !TalkInbox methodsFor: 'accessing - caches' stamp: 'ct 7/14/2021 20:24'! messagesPerContributions "Cached." ^ messagesPerContributions ifNil: [ | dictionary | dictionary := Dictionary new. self messages do: [:message | message contributions do: [:contribution | (dictionary at: contribution ifAbsentPut: [Set new]) add: message]]. messagesPerContributions := dictionary]! ! !TalkInbox methodsFor: 'accessing - caches' stamp: 'ct 8/13/2023 21:20'! messagesPerIds "Cached." ^ messagesPerIds ifNil: [ | dictionary | dictionary := Dictionary new. self messages do: [:message | dictionary at: message messageId put: message]. messagesPerIds := dictionary]! ! !TalkInbox methodsFor: 'comparing' stamp: 'ct 5/7/2021 17:36'! dataKey ^ super dataKey, {self mailingList}! ! !TalkInbox methodsFor: 'sending messages' stamp: 'ct 7/14/2021 18:30'! decorateMessage: aStringOrText ^ self class decorateMessage: aStringOrText! ! !TalkInbox methodsFor: 'sending messages' stamp: 'ct 6/25/2023 21:19'! newMessage | message | message := self mailingList newMessage. message from: MailSender userEmail; to: self mailAddress; body: (self newMessageBodyFor: message body content withBlanksTrimmed). ^ message! ! !TalkInbox methodsFor: 'sending messages' stamp: 'ct 7/15/2021 00:13'! newMessageBodyFor: aStringOrText | plainText | plainText := MIMEDocument contentType: MIMEDocument contentTypePlainText content: aStringOrText. self class sendHtmlMessages ifFalse: [^ plainText]. ^ MIMEDocument newMultipartAlternative addPart: plainText; addPart: (MIMEDocument contentType: MIMEDocument contentTypeHtml content: aStringOrText asText asStringToHtml); yourself! ! !TalkInbox methodsFor: 'initialize-release' stamp: 'ct 5/25/2021 18:32'! defaultDownloadRange ^ 30 days * 3 "months"! ! !TalkInbox methodsFor: 'initialize-release' stamp: 'ct 12/2/2022 00:10'! initialize super initialize. self downloadRange: self defaultDownloadRange. self projects: OrderedCollection new! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 5/25/2021 18:32'! downloadRange ^ downloadRange! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 5/25/2021 18:32'! downloadRange: aDuration downloadRange := aDuration! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 5/7/2021 15:05'! mailingList ^ mailingList! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 5/7/2021 15:05'! mailingList: aMailingList mailingList := aMailingList! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 7/14/2021 21:16'! nabbleNodeId ^ nabbleNodeId! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 7/14/2021 21:16'! nabbleNodeId: anInteger nabbleNodeId := anInteger! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 7/14/2021 21:13'! projects ^ projects! ! !TalkInbox methodsFor: 'accessing - configuration' stamp: 'ct 7/14/2021 21:13'! projects: aCollection projects := aCollection! ! !TalkInbox methodsFor: 'accessing - urls' stamp: 'ct 6/1/2023 18:27'! hyperkittyThreadUrlForMessageId: messageId ^ self hyperkittyUrlForMessageId: messageId thread: true! ! !TalkInbox methodsFor: 'accessing - urls' stamp: 'ct 6/1/2023 18:25'! hyperkittyUrlForMessageId: messageId ^ self hyperkittyUrlForMessageId: messageId thread: false! ! !TalkInbox methodsFor: 'accessing - urls' stamp: 'ct 6/5/2023 00:10'! hyperkittyUrlForMessageId: messageId thread: thread "see: https://gitlab.com/mailman/hyperkitty/-/blob/f8b2bf6e5bfdf7ceada7ad1048f6d039d49fd554/hyperkitty/lib/utils.py#L48" | id hash | id := messageId. (id first = $< and: [id last = $>]) ifTrue: [ id := id allButFirst allButLast]. id := id take: 255. hash := (Base32MimeConverter mimeEncode: (SecureHashAlgorithm new hashMessage: id) talkAsByteArray readStream) contents. ^ 'https://lists.squeakfoundation.org/archives/list/{1}@lists.squeakfoundation.org/{2}/{3}/' format: {self name. thread ifTrue: ['thread'] ifFalse: ['message']. hash}! ! !TalkInbox methodsFor: 'accessing - urls' stamp: 'ct 7/14/2021 21:59'! nabbleUrlForSubject: aString | query | query := 'subject:"{1}"' format: {self nabbleEscape: aString}. ^ 'http://forum.world.st/template/NamlServlet.jtp?macro=search_page&node={1}&sort=date&query={2}' format: {self nabbleNodeId. query encodeForHTTP}! ! !TalkInbox methodsFor: 'accessing - urls' stamp: 'ct 7/14/2021 21:59'! pipermailUrlForMonth: aMonth subject: aString ^ 'http://lists.squeakfoundation.org/pipermail/{1}/{2}/thread.html#:~:text={3}' format: {self name. '{1}-{2}' format: {aMonth year. aMonth monthName}. aString encodeForHTTP}! ! !TalkInbox methodsFor: 'updating' stamp: 'ct 7/8/2021 13:11'! lastRefreshed ^ lastRefreshed! ! !TalkInbox methodsFor: 'updating' stamp: 'ct 8/26/2023 17:56'! refreshMessagePlaceholders messagePlaceholders ifNotNil: [ messagePlaceholders keysAndValuesRemove: [:id :placeholder | placeholder tryToResolve isPlaceholder not]].! ! !TalkInbox methodsFor: 'updating' stamp: 'ct 8/27/2023 21:17'! refreshMessages self mailingList updateMessagesFor: self downloadRange. self projects do: #refreshVersions. self resetCaches. self refreshMessagePlaceholders. lastRefreshed := DateAndTime now. self triggerEvent: #refreshMessages.! ! !TalkInbox methodsFor: 'private' stamp: 'ct 6/15/2021 19:12'! nabbleEscape: aString ^ aString copyWithRegex: '(?<=[\\"])' matchesReplacedWith: '\'! ! !TalkInbox methodsFor: 'private' stamp: 'ct 8/15/2023 23:53'! resetCaches conversationsPerContributions := nil. messagesPerContributions := nil. messagesPerIds := nil. lastRefreshed := nil. self flag: #optimize. "some indices (at least messagesPerIds) could be updated more efficiently if we had a list of new messages to add them"! ! !TalkInbox methodsFor: 'contribution parsing' stamp: 'ct 5/7/2021 19:46'! parseContributionsFrom: aMessage ^ Array streamContents: [:stream | self parseSqueakSourceContributionFrom: aMessage ifFound: [:contribution | stream nextPut: contribution]]! ! !TalkInbox methodsFor: 'contribution parsing' stamp: 'ct 7/14/2021 21:32'! parseSqueakSourceContributionFrom: aMessage ifFound: contributionBlock | contribution | (self squeakSourceMailers includes: aMessage author) ifFalse: [^ nil]. aMessage subject = 'Daily Commit Log' ifTrue: [^ nil]. contribution := TalkRepositoryContribution parseFor: self fromSubject: aMessage subject. contribution ifNil: [ "self notify: 'Unknown SqueakSource mail format!!'." self flag: #todo. "Support old format where version name is in body" ^ nil]. ^ contributionBlock value: contribution! ! !TalkInbox methodsFor: 'contribution parsing' stamp: 'ct 5/7/2021 18:44'! squeakSourceMailers ^ #('commits@source.squeak.org')! ! !TalkInbox methodsFor: 'copying' stamp: 'ct 7/18/2021 17:28'! postCopy super postCopy. self resetCaches.! ! !TalkInbox methodsFor: 'printing' stamp: 'ct 5/7/2021 15:23'! printOn: aStream super printOn: aStream. aStream nextPut: $<; nextPutAll: self name; nextPut: $>! ! !TalkInbox methodsFor: '*SqueakInboxTalkTests-Core-snapshots' stamp: 'ct 6/10/2021 16:21'! talkAPITestTakeSnapshotFor: snapshotter ^ snapshotter takeSnapshotOfInbox: self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! TalkInbox class instanceVariableNames: ''! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 7/1/2023 14:52'! beginners ^ (self on: TalkMailingList beginners) nabbleNodeId: 107673; subjectPrefix: '[Newbies] '; yourself! ! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 6/3/2023 18:29'! etoysDev ^ (self on: TalkMailingList etoysDev) projects: {TalkProject etoys}; nabbleNodeId: 3333966; yourself! ! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 12/2/2022 00:20'! squeakDev ^ (self on: TalkMailingList squeakDev) projects: {TalkProject trunk. TalkProject ffi}, TalkProject squeakVersions reversed; nabbleNodeId: 45488; yourself! ! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 12/2/2022 00:21'! vmBeginners ^ (self on: TalkMailingList vmBeginners) nabbleNodeId: 3068605; yourself! ! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 12/2/2022 00:20'! vmDev ^ (self on: TalkMailingList vmDev) projects: {TalkProject vmMaker}; nabbleNodeId: 104410; yourself! ! !TalkInbox class methodsFor: 'accessing' stamp: 'ct 12/2/2022 00:25'! wellKnownInboxes ^ ((Pragma allNamed: #talkInbox in: self class) , (Pragma allNamed: #talkInbox: in: self class) sorted: [:pragma | pragma numArgs > 0 ifTrue: [pragma argumentAt: 1] ifFalse: [Float infinity]] ascending , [:pragma | pragma selector] ascending) collect: [:pragma | self perform: pragma selector]! ! !TalkInbox class methodsFor: 'initialize-release' stamp: 'ct 11/25/2022 20:55'! cleanUp: aggressive aggressive ifTrue: [ MessageSignature := SendHtmlMessages := nil]. self clearAllCaches! ! !TalkInbox class methodsFor: 'caching' stamp: 'ct 7/23/2021 21:21'! clearAllCaches "Exclude subinstances from global cache reset as they contain configuration. Instead reset their instance-side caches manually." | inboxes | self flag: #discuss. "This is a bit hacky and probably overriding #cache would be more idiomatic, but this would be harder to mock during the tests (see TalkInboxTestResource). Maybe revise this decision later." inboxes := self cache select: [:object | object isKindOf: self]. [ TalkMailingList clearAllCaches. super clearAllCaches] ensure: [ inboxes do: [:inbox | inbox resetCaches; cached]]! ! !TalkInbox class methodsFor: 'sending messages' stamp: 'ct 7/9/2021 19:49'! decorateMessage: aStringOrText | signatureText | signatureText := self messageSignature. signatureText isEmptyOrNil ifTrue: [^ aStringOrText]. self sendHtmlMessages ifTrue: [signatureText := signatureText asTextFromHtml]. ^ '{1}\\{2}' withCRs asText format: {aStringOrText. signatureText}! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 6/1/2023 19:12'! defaultMessageSignature ^ ('---
Sent from {1}
' format: { (self environment classNamed: #TalkInboxBrowser) ifNil: ['Squeak Inbox Talk'] ifNotNil: ['{1}' format: {TalkInboxBrowser appName. TalkInboxBrowser repositoryUrl}]}) asTextFromHtml! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 6/3/2023 20:51'! editMessageSignature "self editMessageSignature" | signature | signature := self sendHtmlMessages ifTrue: [self messageSignature asTextFromHtml] ifFalse: [self messageSignature]. Project uiManager edit: signature label: 'Squeak Inbox Talk message signature' shouldStyle: false accept: [:answer | self messageSignature: (self sendHtmlMessages ifTrue: [answer asStringToHtml] ifFalse: [answer])]! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 8/27/2023 23:36'! enableSemanticSearch ^ EnableSemanticSearch ifNil: [false]! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 8/27/2023 21:35'! enableSemanticSearch: aBoolean aBoolean ifTrue: [ TalkInboxBrowser ensureSemanticsPackageOrCancel ifNil: [^ self]]. EnableSemanticSearch := aBoolean.! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 6/1/2023 19:09'! messageSignature ^ MessageSignature ifNil: [self defaultMessageSignature]! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 7/9/2021 19:15'! messageSignature: aString MessageSignature := aString! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 7/8/2021 18:03'! sendHtmlMessages ^ SendHtmlMessages ifNil: [false]! ! !TalkInbox class methodsFor: 'preferences' stamp: 'ct 7/8/2021 14:07'! sendHtmlMessages: aBoolean SendHtmlMessages := aBoolean! ! !TalkInbox class methodsFor: 'instances' stamp: 'ct 5/19/2021 20:54'! on: aMailingList ^ self new mailingList: aMailingList; cached! ! !TalkInbox class methodsFor: '*SqueakInboxTalkTests-preferences' stamp: 'ct 8/26/2023 03:13'! disableSemanticSearchDuring: aBlock self enableSemanticSearch ifFalse: [^ aBlock value]. self enableSemanticSearch: false. ^ aBlock ensure: [ self enableSemanticSearch: true]! ! !TalkInbox class methodsFor: '*gnucash' stamp: 'jmck 5/18/2024 14:52'! gnucashDevs ^ (self on: TalkMailingList gnucashDev) nabbleNodeId: 1415818; yourself! ! !TalkInbox class methodsFor: '*gnucash' stamp: 'jmck 2/14/2025 21:02'! gnucashUsers ^ self on: TalkMailingList gnucashUser! !