MCSmtpRepository.st
author Claus Gittinger <cg@exept.de>
Sat, 01 Sep 2018 17:33:15 +0200
changeset 1092 8d0ea96a3d72
parent 1022 b561a6a0a2d7
permissions -rw-r--r--
initial checkin class: MCFileTreeFileSystemUtils class: MCFileTreeFileSystemUtils class added:17 methods

"{ Package: 'stx:goodies/monticello' }"

"{ NameSpace: Smalltalk }"

MCWriteOnlyRepository subclass:#MCSmtpRepository
	instanceVariableNames:'email'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Monticello-Repositories'
!


!MCSmtpRepository class methodsFor:'as yet unclassified'!

morphicConfigure
        | dialog address |

        dialog := UIManager isNil ifTrue:[Dialog] ifFalse:[ UIManager default ].
        address := dialog request: 'Email address:' translated.
        ^ address isEmpty ifFalse: [self new emailAddress: address]
! !

!MCSmtpRepository class methodsFor:'queries'!

description
	^ 'SMTP'
! !

!MCSmtpRepository methodsFor:'accessing'!

description
	^ 'mailto://', email
! !

!MCSmtpRepository methodsFor:'as yet unclassified'!

bodyForVersion: aVersion
	^ String streamContents:
		[ :s |
		s nextPutAll: 'from version info:'; cr; cr.
		s nextPutAll:  aVersion info summary]
!

emailAddress: aString
	email := aString	
!

messageForVersion: aVersion
	| message data |
	message := MailMessage empty.
	message setField: 'from' toString: MailSender userName.
	message setField: 'to' toString: email.
	message setField: 'subject' toString: (self subjectForVersion: aVersion). 

	message body:
		(MIMEDocument
			contentType: 'text/plain'
			content: (self bodyForVersion: aVersion)).

	"Prepare the gzipped data"
	data := RWBinaryOrTextStream on: String new.
	aVersion fileOutOn: data.
	message addAttachmentFrom: data reset withName: aVersion fileName.
	^ message
! !

!MCSmtpRepository methodsFor:'printing & storing'!

basicStoreVersion: aVersion
	MailSender sendMessage: (self messageForVersion: aVersion)
! !

!MCSmtpRepository methodsFor:'queries'!

subjectForVersion: aVersion
	^ '[Package] ', aVersion info name
! !

!MCSmtpRepository class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '$Id$'
! !