[ANN] SqueakSource commit emails

stephane ducasse stephane.ducasse at free.fr
Wed Aug 22 06:31:49 UTC 2007


this is cool.
Stef

On 22 août 07, at 01:34, Matthew Fulmer wrote:

> I added a mechanism SqueakSource to send email notifications
> whenever a new version is uploaded.
>
> http://www.squeaksource.com/ss/SqueakSource-mtf.1025.mcz
>
> Features:
> - Configurable recipient and reply-to address, both per project
>   and global default
> - Can be enabled or disabled per-project, or for global default
> - Three types of commit emails, only configurable globally:
>   - Summary only: Sends URL and version summary information.
>     Requires no server-side mcz decoding, so is instantaneous.
>     Importing SqueakSource-mtf.1025.mcz to localhost took 2
>     seconds under this setting.
>   - Summary + full snapshot: additionally puts a text
>     representation of the version in the body of the email. With
>     my experiment, this setting took the longest, since a full
>     snapshot is pretty big.  Importing SqueakSource-mtf.1025.mcz
>     to localhost took 9 seconds under this setting.
>   - Summary + patch: finds the latest ancestor in the project and
>     puts a patch in the body of the email. A sample patch email is
>     forwarded at the end of this email.  I was surprised to find
>     this was faster than the above method; it does 2-3 times more
>     parsing/processing as above, but writes much less data.
>     Importing SqueakSource-mtf.1025.mcz to localhost took 5
>     seconds under this setting.
> - Two new textual representations for generic Monticello packages:
>   MCTextWriter, and MCDiffyTextWriter. They are write-only formats
>   intended for human, rather than computer, consumption. Currently
>   it is grafted on top of the chunk format writer, but I can do
>   better. Next version will feature a much better textual format.
>   These two writer classes have no dependencies on SqueakSource,
>   and could be added directly to Monticello.
>
> Installation Instructions:
>
> These instructions are for merging these features into an
> existing SqueakSource installation. For new installations, see
> http://wiki.squeak.org/squeak/5766 (slightly out of date; I will
> update it soon)
>
> I tested these instructions on a 3.8.1 image running
> SqueakSource-al.1024:
> 1. Merge in SqueakSource-mtf.1025. It is nearly all new classes,
>    and has no core changes, so it probably won't have conflicts.
> 2. log in as superuser
> 3. Go to global edit settings
> 4. Set the 5 options:
>    - SMTP Server
>    - Generated email:           sender address
>    - Default email recipients:  (blank by default)
>    - Default Reply-To Address:  defaults to squeak-dev list
>    - Show in commit notifications: (choose detail level)
>    - Default subscriptions:     (check the checkbox if you want to
>      enable commit emails)
>
> This sets the defaults for all projects. If any per-project
> settings are non-nil, they will ignore the defaults. So, you must
> do this right after installation and before any existing project
> settings have been changed.
>
> Here is a generated commit email (Summary + Patch) for
> SqueakSource-mtf.1025:
>
> ----- Forwarded message from no-reply at localhost -----
>
> To: tapplek at gmail.com
> From: no-reply at localhost
> Date: Tue, 21 Aug 2007 16:05:04 -0700 (MST)
> Subject: SqueakSource: SqueakSource-mtf.1025.mcz
>
> A new version of SqueakSource was added to project SqueakSource:
> http://localhost:8888/ss/SqueakSource-mtf.1025.mcz
>
> ==================== Summary ====================
>
> Name: SqueakSource-mtf.1025
> Author: mtf
> Time: 21 August 2007, 4:03:16 pm
> UUID: e7fe67cd-2502-7f4e-81ce-7681f86bf1d8
> Ancestors: SqueakSource-al.1024
>
> - add model for sending commit emails to SSProject
> - add model for default values of above to SSRepository
> - add two classes for writing text representations of generic  
> Monticello packages: MCTextWriter and MCDiffyTextWriter
> - add three classes for writing text representations SqueakSource  
> versions and packages: SSBasicTextWriter, SSTextWriter, and  
> SSDiffyTextWriter
> - add email sending capabilities via SSEmailSubscription
>
> =============== Diff against SqueakSource-al.1024 ===============
>
> Item was added:
> + ----- Method: SSProject>>subscriptionsDo: (in category 'accessing- 
> subscriptions') -----
> + subscriptionsDo: aBlock
> + 	^ self subscriptions do: aBlock!
>
> Item was added:
> + ----- Method: SSSubscription>>versionAdded:to: (in category 'as  
> yet unclassified') -----
> + versionAdded: aVersion to: aProject
> + 	^ self!
>
> Item was added:
> + SSBasicTextWriter subclass: #SSTextWriter
> + 	instanceVariableNames: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
> +
> + !SSTextWriter commentStamp: '<historical>' prior: 0!
> + In addition to writing summaries, my instances also dump a full  
> snapshot of the uploaded version.
> +
> + For speed notes of this class, see the class comment of  
> SSDiffyTextWriter!
>
> Item was added:
> + ----- Method: MCTextWriter>>writeVersion: (in category 'writing')  
> -----
> + writeVersion: aVersion
> + 	self writeVersionInfo: aVersion info.
> + 	self writeSnapshot: aVersion snapshot.
> + !
>
> Item was added:
> + ----- Method: SSEMailSubscription>>writeHeaders (in category 'as  
> yet unclassified') -----
> + writeHeaders
> + 	sender ifNotEmpty: [	stream nextPutAll: 'From: '; nextPutAll:  
> sender].
> + 	project emailRecipients ifNotEmpty: [stream cr; nextPutAll: 'To:  
> '].
> + 	project emailRecipients
> + 		do: [:email | stream nextPutAll: email address]
> + 		separatedBy: [stream nextPutAll: ', '].
> + 	project replyTo ifNotEmpty: [stream
> + 		cr; nextPutAll: 'Reply-To: '; nextPutAll: project replyTo].
> + 	stream cr;
> + 		nextPutAll: 'Subject: ';
> + 		nextPutAll: project title; nextPutAll: ': ';
> + 		nextPutAll: version fileName; cr; cr!
>
> Item was added:
> + ----- Method: SSDiffyTextWriter>>writePatchHeader: (in category  
> 'as yet unclassified') -----
> + writePatchHeader: info
> + 	self textWriter writePatchHeader: info!
>
> Item was added:
> + ----- Method: SSRepository>>defaultEmailRecipients (in category  
> 'accessing-settings') -----
> + defaultEmailRecipients
> + 	^self properties
> + 		at: #defaultEmailRecipients
> + 		ifAbsent: [OrderedCollection new]!
>
> Item was changed:
>   ----- Method: SSProject>>addVersion:author: (in category  
> 'accessing-versions') -----
>   addVersion: aString author: aUser
>   	| array version |
>   	array := aString asByteArray.
>   	version := SSVersion
>   		array: array
>   		author: aUser.
>   	SSRepository storage saveMonticello: array of: version to: self.
> + 	versions at: version fileName put: version.
> + 	self versionAdded: version.
> + 	^ version
> + 	!
> - 	^versions at: version fileName put: version.
> - 		!
>
> Item was added:
> + ----- Method: SSRepository>>defaultEmailRecipients: (in category  
> 'accessing-settings') -----
> + defaultEmailRecipients: aCollection
> + 	^self properties
> + 		at: #defaultEmailRecipients
> + 		put: aCollection!
>
> Item was added:
> + SSModel subclass: #SSEmailAddress
> + 	instanceVariableNames: 'address'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Model'!
>
> Item was added:
> + ----- Method: SSRepository>>commitWriterClass (in category  
> 'accessing-settings') -----
> + commitWriterClass
> + 	^self properties
> + 		at: #commitWriterClass
> + 		ifAbsent: [SSBasicTextWriter]!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>writerClass (in category 'as  
> yet unclassified') -----
> + writerClass
> + 	^ SSRepository current commitWriterClass!
>
> Item was added:
> + ----- Method: SSRepository>>emailSender: (in category 'accessing- 
> settings') -----
> + emailSender: aString
> + 	^self properties
> + 		at: #emailSender
> + 		put: aString!
>
> Item was added:
> + ----- Method: SSProject>>replyTo (in category 'accessing') -----
> + replyTo
> + 	"Answer the value of replyTo"
> +
> + 	^ replyTo ifNil: [SSRepository current defaultReplyTo]!
>
> Item was added:
> + ----- Method: SSTextWriter>>writeSnapshot: (in category 'as yet  
> unclassified') -----
> + writeSnapshot: snapshot
> + 	self textWriter writeSnapshot: snapshot!
>
> Item was added:
> + ----- Method: SSEmailAddress>>address: (in category 'accessing')  
> -----
> + address: anObject
> + 	"Set the value of address"
> +
> + 	address _ anObject!
>
> Item was added:
> + ----- Method: SSDiffyTextWriter class>>description (in category  
> 'as yet unclassified') -----
> + description
> + 	^ 'Summary + changes'!
>
> Item was added:
> + ----- Method: SSEMailSubscription class>>description (in category  
> 'as yet unclassified') -----
> + description
> + 	^ 'Recieve commit notifications by email'!
>
> Item was added:
> + MCStWriter subclass: #MCTextWriter
> + 	instanceVariableNames: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
> +
> + !MCTextWriter commentStamp: '<historical>' prior: 0!
> + A basic writer for SqueakSource versions and projects. Does no  
> decoding of .mcz files!
>
> Item was added:
> + ----- Method: SSTextWriter class>>description (in category 'as  
> yet unclassified') -----
> + description
> + 	^ 'Summary + full snapshot'!
>
> Item was changed:
>   ----- Method: SSProject>>metaobject (in category 'metamodel') -----
>   metaobject
>   	| metaobject |
>   	metaobject := MWMetaobject for: self.
>   	metaobject textAttribute: #id do: [ :attribute |
>   		attribute
>   			label: 'Name';
>   			maxLength: 20;
>   			addRequiredRule;
>   			addValidationRule: [ :value |
>   				value allSatisfy: [ :char | char isLetter or: [ char  
> isDigit ] ] ]
>   				errorString: 'name should only contain letters and digits';
>   			addValidationRule: [ :value |
>   				SSRepository current isUniqueProjectId: value ]
>   				errorString: 'name is not unique' ].
>   	metaobject textAttribute: #title do: [ :attribute |
>   		attribute
>   			label: 'Title';
>   			maxLength: 50;
>   			addRequiredRule ].
>   	metaobject textAttribute: #description do: [ :attribute |
>   		attribute
>   			label: 'Description';
>   			multiLine: true ].
>   		
>   	metaobject multipleRelationshipAttribute: #tags do: [ :attribute |
>   		attribute
>   			label: 'Tags';
>   			relationshipTo: [ self repository tags ]
>   			formatWith: [ :each | each name ];
>   			"nilItemString: 'none yet';"
>   			yourself ].
>   		
>   	metaobject singleRelationshipAttribute: #license do: [ :attribute |
>   		attribute
>   			label: 'License';
>   			relationshipTo: self licenses
>   				formatWith: [ :each | each isNil
>   					ifTrue: [ 'None' ]
>   					ifFalse: [ each first ifNil: [ 'None' ] ] ] ].
>   		
>   	metaobject booleanAttribute: #canBless do: [:attribute |
>   		attribute
>   			label: 'Enable Blessings'.
>   	].
>
>   	metaobject singleRelationshipAttribute: #globalRight do:  
> [ :attribute |
>   		attribute
>   			label: 'Global';
>   			relationshipTo: SSAccessPolicy globalRights
>   				formatWith: [ :symbol | symbol asCapitalizedPhrase ] ].
>   	metaobject multipleRelationshipAttribute: #admins do:  
> [ :attribute |
>   		attribute
>   			label: 'Administrators';
>   			addValidationRule: [ :admins |
>   				| currentUser |
>   				currentUser := SSSession currentSession user.
>   				currentUser isSuperUser
>   					or: [
>   						admins anySatisfy: [ :each |
>   							each isGroup
>   								ifTrue: [ each hasMember: currentUser ]
>   								ifFalse: [ each = currentUser ] ] ] ]
>   			errorString: 'You can''t remove yourself from the list of  
> administrators';
>   			hide ].
>   	metaobject multipleRelationshipAttribute: #developers do:  
> [ :attribute |
>   		attribute label: 'Developers'; hide ].
>   	metaobject multipleRelationshipAttribute: #guests do:  
> [ :attribute |
>   		attribute label: 'Guests'; hide ].
> +
> + 	metaobject multipleAttribute: #emailRecipients do: [ :attribute |
> + 		attribute
> + 			label: 'Send emails to';
> + 			baseClass: SSEmailAddress].
> + 	
> + 	metaobject textAttribute: #replyTo do: [ :attribute |
> + 		attribute
> + 			label: 'Reply-To Address';
> + 			maxLength: 50].
> + 	
> + 	metaobject multipleRelationshipAttribute: #subscriptions do:  
> [ :attribute |
> + 		attribute
> + 			label: 'Subscriptions';
> + 			relationshipTo: [SSSubscription allSubclasses]].
> +
>   	^metaobject!
>
> Item was added:
> + ----- Method: MCTextWriter>>writeVersionInfo: (in category  
> 'writing') -----
> + writeVersionInfo: aVersionInfo
> + 	stream
> + 		nextPutAll: '==================== Summary  
> ===================='; cr; cr;
> + 		nextPutAll: aVersionInfo summary; cr; cr!
>
> Item was added:
> + ----- Method: SSRepository class>>defaultEmailSender (in category  
> 'private') -----
> + defaultEmailSender
> + 	^'no-reply@', self hostName!
>
> Item was changed:
>   SSModel subclass: #SSProject
> + 	instanceVariableNames: 'id title description creator  
> accessPolicy versions dateCreated feeds wiki blessings configs tags  
> cache license emailAddresses replyTo subscriptions emailRecipients'
> - 	instanceVariableNames: 'id title description creator  
> accessPolicy versions dateCreated feeds wiki blessings configs tags  
> cache license'
>   	classVariableNames: ''
>   	poolDictionaries: ''
>   	category: 'SqueakSource-Model'!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>versionAdded:to: (in category  
> 'as yet unclassified') -----
> + versionAdded: aVersion to: aProject
> + 	sender := SSRepository current emailSender.
> + 	stream := String new writeStream.
> + 	project := aProject.
> + 	version := aVersion.
> + 	self writeHeaders.
> + 	(self writerClass on: stream) writeVersion: aVersion for: aProject.
> + 	self sendMail.!
>
> Item was added:
> + ----- Method: SSEmailAddress>>metaobject (in category  
> 'accessing') -----
> + metaobject
> + 	| metaobject |
> + 	metaobject _ MWMetaobject for: self.
> + 	
> + 	metaobject textAttribute: #address do: [ :attribute |
> + 		attribute
> + 			maxLength: 50;
> + 			addRequiredRule].
> + 	
> + 	^metaobject!
>
> Item was added:
> + ----- Method: MCTextWriter>>writeMethodPreamble: (in category  
> 'writing') -----
> + writeMethodPreamble: definition
> + 	stream
> + 		nextPutAll: '----- Method: ';
> + 		nextPutAll: definition fullClassName;
> + 		nextPutAll: '>>';
> + 		nextPutAll: definition selector;
> + 		nextPutAll: ' (in category ';
> + 		nextPutAll: definition category asString printString;
> + 		nextPutAll: ') -----'; cr!
>
> Item was added:
> + ----- Method: SSEmailAddress>>address (in category 'accessing')  
> -----
> + address
> + 	"Answer the value of address"
> +
> + 	^ address!
>
> Item was added:
> + SSTextWriter subclass: #SSDiffyTextWriter
> + 	instanceVariableNames: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
> +
> + !SSDiffyTextWriter commentStamp: '<historical>' prior: 0!
> + Rather than a full snapshot dump, my instances write a patch from  
> the latest ancestor stored in the project. If no ancestors are in  
> the project, they fall back onto doing a full snapshot.
> +
> + Even though this class does much more decoding of .mcz files than  
> SSTextWriter, it is usually a lot faster because a diff is much  
> less information to write than a full snapshot. As a rough metric,  
> a diff of SqueakSource-mtf.1025 (the package where this class was  
> introduced) took 7 seconds to write (on my computer), while a full  
> snapshot took 33 seconds to write. On the other hand, a version  
> summary was instantaneous, as it requires no decoding of .mcz files!
>
> Item was added:
> + ----- Method: SSRepository>>defaultSubscriptions: (in category  
> 'accessing-settings') -----
> + defaultSubscriptions: aCollection
> + 	^self properties
> + 		at: #defaultSubscriptions
> + 		put: aCollection!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writePatch: (in category  
> 'writing') -----
> + writePatch: aPatch
> + 	aPatch operations do:
> + 		[:ea |
> + 		ea isRemoval ifTrue: [self writeRemoval: ea].
> + 		ea isAddition ifTrue: [self writeAddition: ea].
> + 		ea isModification ifTrue: [self writeModification: ea].
> + 		stream cr.].!
>
> Item was added:
> + MCWriter subclass: #SSBasicTextWriter
> + 	instanceVariableNames: 'textWriter'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
> +
> + !SSBasicTextWriter commentStamp: '<historical>' prior: 0!
> + My instances write version summaries for SqueakSource versions  
> and projects. Does no decoding of .mcz files. Subclasses extend the  
> functionality.
> +
> + For speed notes about this class, see the class comment of  
> SSDiffyTextWriter!
>
> Item was added:
> + ----- Method: SSDiffyTextWriter>>textWriterClass (in category 'as  
> yet unclassified') -----
> + textWriterClass
> + 	^ MCDiffyTextWriter!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>writeSummary (in category 'as  
> yet unclassified') -----
> + writeSummary
> + 	| author |
> + 	author := version authorString ifEmpty: [version guessedAuthor].
> + 	author
> + 		ifNil: [ stream
> + 			nextPutAll: 'A new version of ';
> + 			nextPutAll: version package;
> + 			nextPutAll: ' was added to project ';
> + 			nextPutAll: project title; nextPut: $:; cr]
> + 		ifNotNil: [ stream
> + 			nextPutAll: author;
> + 			nextPutAll: ' uploaded a new version of ';
> + 			nextPutAll: version package;
> + 			nextPutAll: ' to project ';
> + 			nextPutAll: project title; nextPut: $:; cr].
> + 	stream nextPutAll: (version url: project); cr; cr.!
>
> Item was added:
> + ----- Method: MCTextWriter>>chunkContents: (in category  
> 'writing') -----
> + chunkContents: aBlock
> + 	stream nextChunkPut: (String streamContents: aBlock); cr!
>
> Item was added:
> + ----- Method: SSDiffyTextWriter>>writePatch: (in category 'as yet  
> unclassified') -----
> + writePatch: patch
> + 	self textWriter writePatch: patch!
>
> Item was added:
> + ----- Method: TextDiffBuilder>>stringForAttributes: (in category  
> '*SqueakSource-Notifications') -----
> + stringForAttributes: type
> + 	"Private.
> + 	Answer the String that prefixes text of the given type."
> +
> + 	^type caseOf: {
> + 		[#insert] -> [ '+ ' ].
> + 		[#remove] -> [ '- '].
> + 	} otherwise: [ '  ' ].
> + !
>
> Item was added:
> + ----- Method: SSDiffyTextWriter>>writeVersion:for: (in category  
> 'as yet unclassified') -----
> + writeVersion: aSSVersion for: aProject
> + 	| reader ancestor patch |
> + 	reader := aSSVersion reader: aProject.
> + 	ancestor := (aSSVersion versionInfo latestAncestorIn: aProject)
> + 		ifNil: [reader info latestAncestorIn: aProject].
> + 	self writeSummary: aSSVersion for: aProject.
> + 	self writeVersionInfo: aSSVersion versionInfo.
> + 	ancestor
> + 		ifNil: [self writeSnapshot: reader snapshot.]
> + 		ifNotNil: [
> + 			patch := reader snapshot patchRelativeToBase:
> + 				(ancestor reader: aProject) snapshot.
> + 			self writePatchHeader: ancestor versionInfo.
> + 			self writePatch: patch.]!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>sendMail (in category 'as yet  
> unclassified') -----
> + sendMail
> + 	project emailRecipients ifEmpty: [^ self].
> + 	SeasidePlatformSupport
> + 		deliverMailFrom: sender
> + 		to: (project emailRecipients collect: [:email | email address])
> + 		text: stream contents.
> + 	"Workspace new contents: stream contents; openLabel: sender."!
>
> Item was added:
> + ----- Method: SSTextWriter>>writeVersion:for: (in category 'as  
> yet unclassified') -----
> + writeVersion: aSSVersion for: aProject
> + 	| reader |
> + 	reader := aSSVersion reader: aProject.
> + 	self writeSummary: aSSVersion for: aProject.
> + 	self writeVersionInfo: aSSVersion versionInfo.
> + 	self writeSnapshot: reader snapshot.!
>
> Item was added:
> + ----- Method: MCAncestry>>latestAncestorIn: (in category  
> '*SqueakSource') -----
> + latestAncestorIn: aProject
> + 	| ancestor |
> + 	self ancestors ifEmpty: [^ nil].
> + 	self allAncestors do: [:anAncestry |
> + 		ancestor _ aProject versionAt: anAncestry name,'.mcz'.
> + 		ancestor ifNotNil: [^ ancestor]].
> + 	^ nil!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>writeDiffAgainst: (in category  
> 'as yet unclassified') -----
> + writeDiffAgainst: ancestor
> + 	stream nextPutAll: 'Diff against ';
> + 		nextPutAll: ancestor fileName; cr.
> + 	self writeVersion
> + 		!
>
> Item was added:
> + MCTestCase subclass: #MCTextWriterTest
> + 	instanceVariableNames: 'version'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
>
> Item was added:
> + ----- Method: SSProject>>subscriptions: (in category 'accessing- 
> subscriptions') -----
> + subscriptions: aCollection
> + 	"Private. Set the subscriptions"
> + 	subscriptions := aCollection!
>
> Item was added:
> + ----- Method: SSProject>>emailRecipients (in category  
> 'accessing') -----
> + emailRecipients
> + 	"Answer the value of emailAddresses"
> +
> + 	^ emailRecipients ifNil: [SSRepository current  
> defaultEmailRecipients]!
>
> Item was added:
> + ----- Method: SSRepository>>defaultSubscriptions (in category  
> 'accessing-settings') -----
> + defaultSubscriptions
> + 	^self properties
> + 		at: #defaultSubscriptions
> + 		ifAbsent: [OrderedCollection new]!
>
> Item was added:
> + ----- Method: SSProject>>replyTo: (in category 'accessing') -----
> + replyTo: anObject
> + 	"Set the value of replyTo"
> +
> + 	replyTo _ anObject!
>
> Item was added:
> + ----- Method: SSBasicTextWriter>>textWriter (in category 'as yet  
> unclassified') -----
> + textWriter
> + 	^ textWriter ifNil: [textWriter := self textWriterClass on:  
> stream]!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writeModification: (in category  
> 'writing') -----
> + writeModification: aModification
> + 	stream nextPutAll: 'Item was changed:'; cr.
> + 	self writePatchFrom: aModification obsoletion to: aModification  
> definition!
>
> Item was added:
> + SSModel subclass: #SSSubscription
> + 	instanceVariableNames: 'stream project version'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
> +
> + !SSSubscription commentStamp: '<historical>' prior: 0!
> + My insances represent a notification that is sent externally (an  
> email message, for instance) in response to an event (like a commit)!
>
> Item was changed:
>   ----- Method: SSRepository class>>defaultRootUrl (in category  
> 'private') -----
>   defaultRootUrl
> + 	^'http://', self hostName, ':', self defaultPort asString, '/'!
> - 	| hostName |
> - 	hostName := NetNameResolver nameForAddress: (NetNameResolver  
> localHostAddress) timeout: 5.
> - 	hostName ifNil: [hostName := NetNameResolver localAddressString].
> - 	^'http://', hostName, ':', self defaultPort asString, '/'!
>
> Item was added:
> + ----- Method: SSRepository>>commitWriterClass: (in category  
> 'accessing-settings') -----
> + commitWriterClass: aClass
> + 	^self properties
> + 		at: #commitWriterClass
> + 		put: aClass!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writePatchFrom:to: (in category  
> 'writing') -----
> + writePatchFrom: src to: dst
> + 	"src and dst are allowed to bi nil to represent a non-existent  
> source or destination state"
> + 	stream nextPutAll: (TextDiffBuilder
> + 		from: (src ifNotNil: [self visitInFork: src] ifNil: [''])
> + 		to: (dst ifNotNil: [self visitInFork: dst] ifNil: [''])
> + 	) buildTextPatch!
>
> Item was changed:
>   SystemOrganization addCategory: #'SqueakSource-Model'!
>   SystemOrganization addCategory: #'SqueakSource-View'!
>   SystemOrganization addCategory: #'SqueakSource-Server'!
>   SystemOrganization addCategory: #'SqueakSource-Tests'!
> + SystemOrganization addCategory: #'SqueakSource-Notification'!
>
> Item was added:
> + ----- Method: SSBasicTextWriter>>writeVersionInfo: (in category  
> 'as yet unclassified') -----
> + writeVersionInfo: info
> + 	self textWriter writeVersionInfo: info!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writeRemoval: (in category  
> 'writing') -----
> + writeRemoval: aRemoval
> + 	stream nextPutAll: 'Item was removed:'; cr.
> + 	self writePatchFrom: aRemoval definition to: nil!
>
> Item was added:
> + ----- Method: MCTextWriter>>visitMethodDefinition: (in category  
> 'visiting') -----
> + visitMethodDefinition: definition
> + 	self writeMethodPreamble: definition.
> + 	self writeMethodSource: definition.
> + 	stream cr!
>
> Item was changed:
>   ----- Method: SSProject>>initialize (in category  
> 'initialization') -----
>   initialize
>   	super initialize.
>   	id := title := description := String new.
>   	accessPolicy := SSAccessPolicy new.
>   	versions := Dictionary new.
>   	dateCreated := Date today.
>   	tags := SortedCollection new.
> + 	cache := IdentityDictionary new.!
> - 	cache := IdentityDictionary new!
>
> Item was added:
> + ----- Method: SSRepository class>>hostName (in category  
> 'private') -----
> + hostName
> + 	^ (NetNameResolver nameForAddress: (NetNameResolver  
> localHostAddress) timeout: 5)
> + 		ifNil: [NetNameResolver localAddressString]!
>
> Item was added:
> + MCTextWriter subclass: #MCDiffyTextWriter
> + 	instanceVariableNames: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
>
> Item was added:
> + ----- Method: SSBasicTextWriter class>>description (in category  
> 'as yet unclassified') -----
> + description
> + 	^ 'Summary only'!
>
> Item was added:
> + ----- Method: SSProject>>versionAdded: (in category 'accessing- 
> subscriptions') -----
> + versionAdded: aVersion
> + 	^ self subscriptionsDo: [:each | each new versionAdded: aVersion  
> to: self]!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writePatchHeader: (in category  
> 'writing') -----
> + writePatchHeader: info
> + 	stream
> + 		nextPutAll: '=============== Diff against ';
> + 		nextPutAll: info name;
> + 		nextPutAll: ' ==============='; cr; cr!
>
> Item was added:
> + ----- Method: SSEMailSubscription>>writeVersion (in category 'as  
> yet unclassified') -----
> + writeVersion
> + 	| ancestor aVersion|
> + 	ancestor := version lastAncestorIn: project.
> + 	aVersion := (version reader: project) version.
> + 	ancestor
> + 		ifNotNil: [(MCDiffyTextWriter on: stream) writeVersion:
> + 			(aVersion asDiffAgainst: (ancestor reader: project) version)]
> + 		ifNil: [(MCTextWriter on: stream) writeVersion: aVersion]
> + 		!
>
> Item was added:
> + ----- Method: SSSubscription class>>renderOn: (in category 'as  
> yet unclassified') -----
> + renderOn: html
> + 	html text: self description!
>
> Item was added:
> + SSSubscription subclass: #SSEMailSubscription
> + 	instanceVariableNames: 'sender'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'SqueakSource-Notification'!
>
> Item was added:
> + ----- Method: TextDiffBuilder>>printTextPatchSequence:on: (in  
> category '*SqueakSource-Notifications') -----
> + printTextPatchSequence: seq on: aStream
> + 	seq do: [:assoc | aStream
> + 		nextPutAll: (self stringForAttributes: assoc key);
> + 		nextPutAll: assoc value; cr]!
>
> Item was changed:
>   ----- Method: SSRepository>>metaobject (in category 'accessing')  
> -----
>   metaobject
>   	| metaobject |
>   	metaobject _ MWMetaobject for: self.
>
>   	metaobject textAttribute: #rootUrl do: [ :attribute |
>   		attribute label: 'Root URL';
>   			addRequiredRule].
>   	metaobject integerAttribute: #port do: [ :attribute |
>   		attribute label: 'Port';
>   			addValidationRule: [ :value | value notNil ]
>   				errorString: 'invalid number';
>   			addValidationRule: [ :value | value between: 1 and: 65535 ]
>   				errorString: 'invalid port';
>   			addRequiredRule].
>   	metaobject textAttribute: #smtpServer do: [ :attribute |
>   		attribute label: 'SMTP server';
>   			addRequiredRule].
>   	metaobject textAttribute: #superUserEmail do: [ :attribute |
>   		attribute label: 'Admin email';
>   			addRequiredRule].
> + 	metaobject textAttribute: #emailSender do: [ :attribute |
> + 		attribute label: 'Generated email';
> + 			addRequiredRule].
> + 	metaobject multipleAttribute: #defaultEmailRecipients do:  
> [ :attribute |
> + 		attribute label: 'Default email recipients'; baseClass:  
> SSEmailAddress].
> + 	metaobject textAttribute: #defaultReplyTo do: [ :attribute |
> + 		attribute label: 'Default Reply-To Address'; maxLength: 50].
> + 	metaobject singleRelationshipAttribute: #commitWriterClass do:  
> [ :attribute |
> + 		attribute label: 'Show in commit notifications';
> + 		relationshipTo: [SSBasicTextWriter withAllSubclasses];
> + 		formatWith: [ :class | class description]].
> + 	metaobject multipleRelationshipAttribute: #defaultSubscriptions  
> do: [ :attribute |
> + 		attribute label: 'Default subscriptions'; relationshipTo:  
> [SSSubscription allSubclasses]].
>   	metaobject booleanAttribute: #allowRegisterProject do:  
> [ :attribute |
>   		attribute label: 'Everyone can register projects'].
>   	metaobject booleanAttribute: #allProjectsVisible do: [ :attribute |
>   		attribute label: 'Everyone can see all projects' ].
>   	metaobject booleanAttribute: #allowCreateTag do: [ :attribute |
>   		attribute label: 'Everyone can create tags'].
>   	metaobject integerAttribute: #batchSize do: [ :attribute |
>   		attribute label: 'Batch size for table reports';
>   			addValidationRule: [ :value | value notNil ]
>   				errorString: 'invalid number';
>   			addValidationRule: [ :value | value > 1 ]
>   				errorString: 'too small';
>   			addRequiredRule].
>   	metaobject colorAttribute: #styleColor do: [ :attribute |
>   		attribute label: 'Style color';
>   			addValidationRule: [ :value | value ~= Color white ]
>   			errorString: 'invalid color'].
>   	metaobject textAttribute: #introText do: [ :attribute |
>   		attribute label: 'Override home text';
>   			multiLine: true].
>   	metaobject textAttribute: #timezone do: [ :attribute |
>   		attribute label: 'Timezone';
>   			addRequiredRule ].
>   	metaobject textAttribute: #googleAnalyticsAccount do:  
> [ :attribute |
>   		attribute label: 'Google Analytics Account' ].
>   	^metaobject!
>
> Item was added:
> + ----- Method: SSBasicTextWriter>>textWriterClass (in category 'as  
> yet unclassified') -----
> + textWriterClass
> + 	^ MCTextWriter!
>
> Item was changed:
>   ----- Method: SSProjectEditor>>renderMainOn: (in category  
> 'rendering') -----
>   renderMainOn: html	
> + 	self isSubForm ifTrue: [^ super renderMainOn: html].
>   	self renderIntroductionTextOn: html.
>   	html layoutTable: [
>   		self renderValidationErrorsOn: html.
>   		self renderFieldsOn: html.
>   		self renderMemberListForAttribute: (self metaobject  
> attributeOf: #admins) on: html.
>   		self renderMemberListForAttribute: (self metaobject  
> attributeOf: #developers) on: html.
>   		self renderMemberListForAttribute: (self metaobject  
> attributeOf: #guests) on: html.
>   		html tableRowWith: [ html space ] span: 2.
>   		html tableRowWith: [ self renderButtonsOn: html ] span: 2 ]!
>
> Item was added:
> + ----- Method: SSRepository>>defaultReplyTo: (in category  
> 'accessing-settings') -----
> + defaultReplyTo: aString
> + 	^self properties
> + 		at: #defaultReplyTo
> + 		put: aString!
>
> Item was added:
> + ----- Method: SSBasicTextWriter>>writeVersion:for: (in category  
> 'as yet unclassified') -----
> + writeVersion: aSSVersion for: aProject
> + 	self writeSummary: aSSVersion for: aProject.
> + 	self writeVersionInfo: aSSVersion versionInfo.!
>
> Item was added:
> + ----- Method: MCTextWriterTest>>testWriteSnapshot (in category  
> 'as yet unclassified') -----
> + testWriteSnapshot
> + 	Workspace new contents: (String streamContents: [:aStream |  
> (MCTextWriter on: aStream) writeSnapshot: self mockSnapshot]);  
> openLabel: 'pizza'.
> + !
>
> Item was added:
> + ----- Method: SSRepository>>emailSender (in category 'accessing- 
> settings') -----
> + emailSender
> + 	^self properties
> + 		at: #emailSender
> + 		ifAbsent: [self class defaultEmailSender]!
>
> Item was added:
> + ----- Method: MCTextWriter>>visitInFork: (in category 'visiting')  
> -----
> + visitInFork: aDefinition
> + 	^ String streamContents: [ :forkedStream |
> + 		aDefinition accept: (self class on: forkedStream)]!
>
> Item was added:
> + ----- Method: MCTextWriter>>writeSnapshot: (in category  
> 'writing') -----
> + writeSnapshot: aSnapshot
> + 	stream nextPutAll: '==================== Snapshot  
> ===================='; cr; cr.
> + 	super writeSnapshot: aSnapshot
> + !
>
> Item was added:
> + ----- Method: SSBasicTextWriter>>writeSummary:for: (in category  
> 'as yet unclassified') -----
> + writeSummary: aSSVersion for: aProject
> + 	| author |
> + 	author := aSSVersion authorString ifEmpty: [aSSVersion  
> guessedAuthor].
> + 	author
> + 		ifNil: [ stream
> + 			nextPutAll: 'A new version of ';
> + 			nextPutAll: aSSVersion package;
> + 			nextPutAll: ' was added to project ';
> + 			nextPutAll: aProject title; nextPut: $:; cr]
> + 		ifNotNil: [ stream
> + 			nextPutAll: author;
> + 			nextPutAll: ' uploaded a new version of ';
> + 			nextPutAll: aSSVersion package;
> + 			nextPutAll: ' to project ';
> + 			nextPutAll: aProject title; nextPut: $:; cr].
> + 	stream nextPutAll: (aSSVersion url: aProject); cr; cr.!
>
> Item was added:
> + ----- Method: SSRepository>>defaultReplyTo (in category  
> 'accessing-settings') -----
> + defaultReplyTo
> + 	^self properties
> + 		at: #defaultReplyTo
> + 		ifAbsent: ['squeak-dev at lists.squeakfountation.org']!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writeVersion: (in category  
> 'writing') -----
> + writeVersion: aVersion
> + 	self writeVersionInfo: aVersion info.
> + 	self writePatchHeader: aVersion baseInfo.
> + 	self writePatch: aVersion patch.!
>
> Item was added:
> + ----- Method: TextDiffBuilder>>buildTextPatch (in category  
> '*SqueakSource-Notifications') -----
> + buildTextPatch
> + 	^String streamContents:[:stream|
> + 		self printTextPatchSequence: self buildPatchSequence on: stream.
> + 	]!
>
> Item was added:
> + ----- Method: SSProject>>emailRecipients: (in category  
> 'accessing') -----
> + emailRecipients: anObject
> + 	"Set the value of emailAddresses"
> +
> + 	emailRecipients _ anObject!
>
> Item was added:
> + ----- Method: MCDiffyTextWriter>>writeAddition: (in category  
> 'writing') -----
> + writeAddition: anAddition
> + 	stream nextPutAll: 'Item was added:'; cr.
> + 	self writePatchFrom: nil to: anAddition definition!
>
> Item was added:
> + ----- Method: SSProject>>subscriptions (in category 'accessing- 
> subscriptions') -----
> + subscriptions
> + 	"Answers the instances of SSSubscription who are interested in  
> changes to this project"
> + 	^ subscriptions ifNil: [self repository defaultSubscriptions]!
>
> Item was added:
> + ----- Method: MCTextWriter>>writeDefinitions: (in category  
> 'writing') -----
> + writeDefinitions: aCollection
> + 	(MCDependencySorter sortItems: aCollection)
> + 		do: [:ea | ea accept: self. stream cr]
> + 		displayingProgress: 'Writing definitions...'.!
>
>
> ----- End forwarded message -----
>
> -- 
> Matthew Fulmer -- http://mtfulmer.wordpress.com/
> Help improve Squeak Documentation: http://wiki.squeak.org/squeak/808
>
>




More information about the Squeak-dev mailing list