Is there one available? I'm trying to automatically send email from one
win32 computer. |
Jerome,
"Jerome Chan" <[hidden email]> wrote in message news:[hidden email]... > Is there one available? I'm trying to automatically send email from one > win32 computer. I've been looking at the same sort of thing. The SMTP part is pretty simple (you can even experiment using a telnet client), but retrieving MX records from a DNS server (to translate a domain name to an actual mail server name or address) is considerably less straightforward. Unless you really need SMTP (writing an e-mail client or bulk mailer?), something like MAPI or CDO (wrapping ADO) or Outlook's object model works really well from within Dolphin. Not to mention its being considerably less arcane. Don |
Don Rylander wrote:
> > I've been looking at the same sort of thing. The SMTP part is pretty simple > (you can even experiment using a telnet client), but retrieving MX records > from a DNS server (to translate a domain name to an actual mail server name > or address) is considerably less straightforward. I don't think you have to bother with the MX records in the typical case. Just open a connection to your own SMTP server -- e.g. your own ISP -- and send. It'll then forward appropriately. I may be wrong, though, I haven't actually written an email client yet... -- chris |
"Chris Uppal" <[hidden email]> wrote in message
news:[hidden email]... > Don Rylander wrote: > > > > I've been looking at the same sort of thing. The SMTP part is pretty > simple > > (you can even experiment using a telnet client), but retrieving MX records > > from a DNS server (to translate a domain name to an actual mail server > name > > or address) is considerably less straightforward. > > I don't think you have to bother with the MX records in the typical case. > Just open a connection to your own SMTP server -- e.g. your own ISP -- and > send. It'll then forward appropriately. Thanks Chris, I hadn't really thought about that, so I wanted to try it before responding. I think that used to be the case, but with spam having become such a problem, most ISPs are more careful about forwarding e-mail to other domains. For example, I can't use an SMTP connection to my home ISP to send a note to myself at work, nor can I go the other way (via SMTP from my work mail server to my home address). If I attach directly to the SMTP server that handles a particular domain, however, there's no problem. For a quick-and-dirty solution to the problem, you could always take a more unix-like approach, using something like nslookup (included with NT and Win 2000) or dig to get the MX record into a file or pipe, then going ahead with the SMTP part. > > I may be wrong, though, I haven't actually written an email client yet... > > -- chris > > Don |
Don Rylander wrote:
> > I don't think you have to bother with the MX records in the typical case. > > Just open a connection to your own SMTP server -- e.g. your own ISP -- and > > send. It'll then forward appropriately. > > Thanks Chris, I hadn't really thought about that, so I wanted to try it before > responding. I think that used to be the case, but with spam having become such > a problem, most ISPs are more careful about forwarding e-mail to other domains. > For example, I can't use an SMTP connection to my home ISP to send a note to > myself at work, nor can I go the other way (via SMTP from my work mail server > to my home address). If I attach directly to the SMTP server that handles a > particular domain, however, there's no problem. Ah, yes. I have heard of similar problems. (And would have encountered them too, I imagine, if I'd actually tried this!) One approach that ISPs can use is to validate incoming connections directly from a list of known "acceptable" IP addresses. Another (more flexible) is to refuse SMTP connections from IP addresses which haven't successfully done a POP3 (or similar) login in the previous <n> minutes. I *suspect* that your ISP is using something similar, or how else could an ordinary brain-damaged client like M$ Outlook (spit!) send email at all. Apparently Demon uses the former technique; the email provider that my employer's offsite machines use to email us error messages uses the latter. Come to think of it, there's no reason why an SMTP server should accept incoming connections, even if they *are* going to submit email for subdomains it "owns". That too is a standing invitation to spam. I guess the bottom line is that you can only send SMTP email by finding a supplier, finding out what validation critia it uses, and meeting them. Oh, well... > Don -- chris P.S. Or talk HTTP to Hotmail... |
Here is a simple SMTP classs. The clever parts are from Squeak.
The bits I wrote do work but are not pretty. Its not finished yet. To send a quick note. n := NetSMTP newIP: ''62.253.162.40''. n mailFrom: ''[hidden email]'' To: ''[hidden email]'' Subject: ''test'' TextMessage: '' hello'' send a file. n mailFrom: ''[hidden email]'' To: ''[hidden email]'' Subject: ''Test of my mail software'' File: ''c:\mime\mime.htm'' Type: ''text/html''. You can send things like html files and .doc files. The guys at work are always hacking around with activeX libraries to do this sort of thing and it usually takes more effort to create the controlling objects than it does to just open a socket on port 25. Cheers Alban ---- CUT HERE --- | package | package := Package name: 'Albans Changes'. package paxVersion: 0; basicComment: 'A set of classes to support email.'. package basicPackageVersion: ''. "Add the package scripts" "Add the class names, loose method names, global names, resource names" package classNames add: #Base64MimeConverter; add: #Mimeconverter; add: #NetSMTP; add: #RWBinaryOrTextStream; yourself. package methodNames add: #Character -> #asCharacter; add: #Collection -> #doWithIndex:; add: #Integer -> #benchFib; add: #Object -> #ifNil:; add: #Object -> #ifNil:ifNotNil:; add: #Object -> #ifNotNil:; add: #SequenceableCollection -> #copyUpTo:; add: #SequenceableCollection -> #first:; add: #UndefinedObject -> #ifNil:; add: #UndefinedObject -> #ifNil:ifNotNil:; add: #UndefinedObject -> #ifNotNil:; yourself. package globalNames yourself. package resourceNames yourself. "Binary Global Names" package binaryGlobalNames: (Set new yourself). "Resource Names" package allResourceNames: (Set new yourself). "Add the prerequisite names" package setPrerequisites: (IdentitySet new add: 'Dolphin'; add: 'Sockets Connection'; yourself). package! "Class Definitions"! Object subclass: #Mimeconverter instanceVariableNames: 'dataStream mimeStream' classVariableNames: '' poolDictionaries: '' classInstanceVariableNames: ''! Object subclass: #NetSMTP instanceVariableNames: 'iString oString iStream oStream socket status sender recpt svr log cr resp mimeType' classVariableNames: '' poolDictionaries: '' classInstanceVariableNames: ''! Mimeconverter subclass: #Base64MimeConverter instanceVariableNames: 'data' classVariableNames: 'FromCharTable ToCharTable' poolDictionaries: '' classInstanceVariableNames: ''! ReadWriteStream subclass: #RWBinaryOrTextStream instanceVariableNames: 'isBinary' classVariableNames: '' poolDictionaries: '' classInstanceVariableNames: ''! "Loose Methods"! !Character methodsFor! asCharacter ^self.! ! !Character categoriesFor: #asCharacter!*-unclassified!public! ! !Collection methodsFor! doWithIndex: aBlock2 " from Squeak." | index | index := 0. self do: [ :item | aBlock2 value: item value: ( index := index +1 )]! ! !Collection categoriesFor: #doWithIndex:!feature from Squeak!public! ! !Integer methodsFor! benchFib "from Squeak :- ( result // seconds to run) = approx calls per second | r t | t := Time millisecondsToRun: [ r := 26 benchFib ]. ( r*1000) // t Squeak and Dolphin compared:- PII233 Dolphin Squeak ratio 30 2558 4016 1.56 35 28837 45375 1.57 40 317104 503313 1.58 ratio remains roughly the same. " ^ self < 2 ifTrue: [1] ifFalse: [ (self -1) benchFib + (self -2) benchFib + 1]! ! !Integer categoriesFor: #benchFib!*-unclassified!public! ! !Object methodsFor! ifNil: aBlock "from Squeak. but in proto object" ^self ! ifNil: nilBlock ifNotNil: ifNotNilBlock "Squeakishly Evaluate the block." ^ifNotNilBlock value! ifNotNil: ifNotNilBlock "Squeakism from squeak protoObject" ^ifNotNilBlock value. ! ! !Object categoriesFor: #ifNil:!*-unclassified!public! ! !Object categoriesFor: #ifNil:ifNotNil:!*-unclassified!public! ! !Object categoriesFor: #ifNotNil:!*-unclassified!public! ! !SequenceableCollection methodsFor! copyUpTo: anElement "copy up to..." ^self first: ( self indexOf: anElement ifAbsent: [ ^ self copy]) -1! first: n "Squeakism to answer the first n elements" ^ self copyFrom: 1 to: n! ! !SequenceableCollection categoriesFor: #copyUpTo:!*-unclassified!public! ! !SequenceableCollection categoriesFor: #first:!*-unclassified!public! ! !UndefinedObject methodsFor! ifNil: aBlock "from Squeak." ^ aBlock value! ifNil: nilBlock ifNotNil: notNilBlock "squeakishly nil about" ^nilBlock value! ifNotNil: aBlock "another squeakism" ^self ! ! !UndefinedObject categoriesFor: #ifNil:!feature from Squeak!public! ! !UndefinedObject categoriesFor: #ifNil:ifNotNil:!*-unclassified!public! ! !UndefinedObject categoriesFor: #ifNotNil:!*-unclassified!public! ! "End of package definition"! Mimeconverter comment: 'Taken from squeak. So far base64 converter is working. (sort of) Must have RWBinaryOrTextArray as input.'! Mimeconverter guid: (GUID fromString: '{C18C60D1-DEF7-11D4-851C-0010A4E62BB0}')! !Mimeconverter categoriesForClass!Unclassified! ! !Mimeconverter methodsFor! dataStream ^dataStream.! dataStream: anObject dataStream := anObject.! mimeDecode "convert from mimeStream to dataStream." self subclassResponsibility.! mimeEncode "from dataStream -> mimeStream" self subclassResponsibility.! mimeStream ^mimeStream.! mimeStream: anObject mimeStream:=anObject.! ! !Mimeconverter categoriesFor: #dataStream!*-unclassified!public! ! !Mimeconverter categoriesFor: #dataStream:!*-unclassified!public! ! !Mimeconverter categoriesFor: #mimeDecode!*-subclass responsibility!*-unclassified!public! ! !Mimeconverter categoriesFor: #mimeEncode!*-subclass responsibility!*-unclassified!public! ! !Mimeconverter categoriesFor: #mimeStream!*-unclassified!public! ! !Mimeconverter categoriesFor: #mimeStream:!*-unclassified!public! ! NetSMTP comment: 'simple SMTP message sender. (Alban) There is nothing fancy about this its not event driven, multithreaded or anything. This is single part mime. examples Note the mime type is explicit. '! NetSMTP guid: (GUID fromString: '{6750ED90-E425-11D4-8527-0010A4E62BB0}')! !NetSMTP categoriesForClass!Unclassified! ! !NetSMTP methodsFor! checkResponse " make sure response is in the 200-300s" (#( 2 3 ) includes: ( resp // 100 )) ifFalse: [ self close. self error: iString. ]! close "shut down" self socket close.! connect "to the server" socket connect. self log: 'connect'.! debug: aBool "change logging" log := aBool. ! dot "send request to server." self log: 'dot'. self resetOut. oStream cr; nextPut: $.; cr. socket sendByteArray: oStream contents asByteArray. ! host: asString "what are we connecting too." svr := InternetAddress fromString: asString.! initialize: asString "set the object up" log:=false. cr := #[ 13 10]. resp:=0. mimeType:='text/plain'. self host: asString; resetIn; resetOut; makeSocket. ! log: aString "report event to transcript log." log ifFalse: [ ^self]. Transcript nextPutAll: 'NetSMTP:' ; display: Date today; nextPut: $,; display: Time now; tab ; nextPut: aString; cr; flush. ! log: aString with: bString "report event to transcript log." log ifFalse: [ ^self]. Transcript nextPutAll: 'NetSMTP:' ; display: Date today; nextPut: $,; display: Time now; tab ; nextPut: aString ; nextPut: bString; cr; flush. ! mailFrom: fromString To: toString Subject: subjString File: fileString Type: aType | enc res aFile inFile | "This just sends a quick text message" mimeType:=aType. aFile := File open: fileString. inFile := aFile readWriteStream. inFile setToEnd. enc := RWBinaryOrTextStream on: (String new: (aFile size) ). enc reset. enc nextPutAll: inFile contents. aFile close. res := Base64MimeConverter mimeEncode: enc. self debug: true. self connect. self reply. self request: 'HELO'. self reply. self request: 'MAIL FROM:<' with: fromString with: '> '. self reply. self request: 'RCPT TO:<' with: toString with: '> '. self reply. self request: 'DATA'. self reply. self request: 'MIME-Version: 1.0'. self request: 'Content-type: ' with: mimeType. self request: 'Content-transfer-encoding: base64'. self request: 'FROM: ' with: fromString. self request: 'TO:' with: toString. self request: 'SUBJECT: ' with: subjString. self requestCR. " Break very long line into smaller parts " self request: res contents. self dot. self reply. self request: 'QUIT'. self close. ! mailFrom: fromString To: toString Subject: subjString Message: textString Type: aType | enc res | "This just sends a quick text message" mimeType := aType. enc := RWBinaryOrTextStream on: (String new: (textString size * 3 // 4) ). enc nextPutAll: textString. res := Base64MimeConverter mimeEncode: enc. self debug: true. self connect. self reply. self request: 'HELO'. self reply. self request: 'MAIL FROM:<' with: fromString with: '> '. self reply. self request: 'RCPT TO:<' with: toString with: '> '. self reply. self request: 'DATA'. self reply. self request: 'MIME-Version: 1.0'. self request: 'Content-type: ' with: mimeType with: '; charset="us-ascii"'. self request: 'Content-transfer-encoding: base64'. self request: 'FROM: ' with: fromString. self request: 'TO:' with: toString. self request: 'SUBJECT: ' with: subjString. self requestCR. self request: res contents. self dot. self reply. self request: 'QUIT'. self close. ! mailFrom: fromString To: toString Subject: subjString TextMessage: textString | enc res | "This just sends a quick text message" enc := RWBinaryOrTextStream on: (String new: (textString size * 3 // 4) ). enc nextPutAll: textString. res := Base64MimeConverter mimeEncode: enc. self debug: true. self connect. self reply. self request: 'HELO'. self reply. self request: 'MAIL FROM:<' with: fromString with: '> '. self reply. self request: 'RCPT TO:<' with: toString with: '> '. self reply. self request: 'DATA'. self reply. self request: 'MIME-Version: 1.0'. self request: 'Content-type: ' with: mimeType with: '; charset="us-ascii"'. self request: 'Content-transfer-encoding: base64'. self request: 'FROM: ' with: fromString. self request: 'TO:' with: toString. self request: 'SUBJECT: ' with: subjString. self requestCR. self request: res contents. self dot. self reply. self request: 'QUIT'. self close. ! mailFrom: fromString To: toString TextMessage: textString | enc res | "This just sends a quick text message" enc := RWBinaryOrTextStream on: (String new: (textString size * 3 // 4) ). enc nextPutAll: textString. res := Base64MimeConverter mimeEncode: enc. self debug: true. self connect. self reply. self request: 'HELO'. self reply. self request: 'MAIL FROM:<' with: fromString with: '> '. self reply. self request: 'RCPT TO:<' with: toString with: '> '. self reply. self request: 'DATA'. self reply. self request: 'MIME-Version: 1.0'. self request: 'Content-type: ' with: mimeType with: '; charset="us-ascii"'. self request: 'Content-transfer-encoding: base64'. self request: 'FROM: ' with: fromString. self request: 'TO:' with: toString. self request: 'SUBJECT: MAIL MESSAGE'. self request: 'DATE:' with: (Date today) printString. self requestCR. self request: res contents. self dot. self reply. self request: 'QUIT'. self close. ! makeSocket "create the client socket" socket := Socket port: 25 address: svr. self log: 'make socket'.! reply "get server reply - wait until reply available." | s | self resetIn. [ socket hasInput ] whileFalse: []. " block until input" [ socket hasInput] whileTrue: [ iStream nextPut: ( socket receiveByte asCharacter)]. iStream position: 0. s := (iStream contents). ((s at: 1) isDigit ) ifTrue: [ resp := ( s copyFrom: 1 to: 3) asNumber]. self log: 'reply ' with: s. self checkResponse. ^s! request: aString "send request to server." self log: 'request' with: aString. self resetOut. oStream nextPutAll: aString; cr. socket sendByteArray: oStream contents asByteArray. ! request: aString with: bString "send request to server." self log: 'request' with: aString. self resetOut. oStream nextPutAll: aString; nextPutAll: bString; cr. socket sendByteArray: oStream contents asByteArray. ! request: aString with: bString with: cString "send request to server." self log: 'request' with: aString. self resetOut. oStream nextPutAll: aString; nextPutAll: bString; nextPutAll: cString; cr. socket sendByteArray: oStream contents asByteArray. ! requestCR "send CR to server." self log: 'requestCR'. self resetOut. oStream cr. socket sendByteArray: oStream contents asByteArray. ! resetIn " clear input." iString := String new: 80. iStream := ReadWriteStream on: iString. self log: 'resetIn.'! resetOut "clear output." oString := String new: 80. oStream := ReadWriteStream on: oString. self log: 'resetOut'.! socket "return the socket." ^socket.! ! !NetSMTP categoriesFor: #checkResponse!*-unclassified!public! ! !NetSMTP categoriesFor: #close!*-unclassified!public! ! !NetSMTP categoriesFor: #connect!*-unclassified!public! ! !NetSMTP categoriesFor: #debug:!*-unclassified!public! ! !NetSMTP categoriesFor: #dot!*-unclassified!public! ! !NetSMTP categoriesFor: #host:!*-unclassified!public! ! !NetSMTP categoriesFor: #initialize:!*-unclassified!public! ! !NetSMTP categoriesFor: #log:!*-unclassified!public! ! !NetSMTP categoriesFor: #log:with:!*-unclassified!public! ! !NetSMTP categoriesFor: #mailFrom:To:Subject:File:Type:!*-unclassified!public! ! !NetSMTP categoriesFor: #mailFrom:To:Subject:Message:Type:!*-unclassified!public! ! !NetSMTP categoriesFor: #mailFrom:To:Subject:TextMessage:!*-unclassified!public! ! !NetSMTP categoriesFor: #mailFrom:To:TextMessage:!*-unclassified!public! ! !NetSMTP categoriesFor: #makeSocket!*-unclassified!public! ! !NetSMTP categoriesFor: #reply!*-unclassified!public! ! !NetSMTP categoriesFor: #request:!*-unclassified!public! ! !NetSMTP categoriesFor: #request:with:!*-unclassified!public! ! !NetSMTP categoriesFor: #request:with:with:!*-unclassified!public! ! !NetSMTP categoriesFor: #requestCR!*-unclassified!public! ! !NetSMTP categoriesFor: #resetIn!*-unclassified!public! ! !NetSMTP categoriesFor: #resetOut!*-unclassified!public! ! !NetSMTP categoriesFor: #socket!*-unclassified!public! ! !NetSMTP class methodsFor! newIP: asString ^(super new) initialize: asString. ! ! !NetSMTP class categoriesFor: #newIP:!*-unclassified!public! ! Base64MimeConverter comment: 'This class encodes and decodes data in Base64 format. This is MIME encoding. We translate a whole stream at once, taking a Stream as input and giving one as output. Returns a whole stream for the caller to use. 0 A 17 R 34 i 51 z 1 B 18 S 35 j 52 0 2 C 19 T 36 k 53 1 3 D 20 U 37 l 54 2 4 E 21 V 38 m 55 3 5 F 22 W 39 n 56 4 6 G 23 X 40 o 57 5 7 H 24 Y 41 p 58 6 8 I 25 Z 42 q 59 7 9 J 26 a 43 r 60 8 10 K 27 b 44 s 61 9 11 L 28 c 45 t 62 + 12 M 29 d 46 u 63 / 13 N 30 e 47 v 14 O 31 f 48 w (pad) = 15 P 32 g 49 x 16 Q 33 h 50 y Outbound: bytes are broken into 6 bit chunks, and the 0-63 value is converted to a character. 3 data bytes go into 4 characters. Inbound: Characters are translated in to 0-63 values and shifted into 8 bit bytes. (See: N. Borenstein, Bellcore, N. Freed, Innosoft, Network Working Group, Request for Comments: RFC 1521, September 1993, MIME (Multipurpose Internet Mail Extensions) Part One: Mechanisms for Specifying and Describing the Format of Internet Message Bodies. Sec 6.2) By Ted Kaehler, based on Tim Olson''s Base64Filter. '! Base64MimeConverter guid: (GUID fromString: '{C18C60D3-DEF7-11D4-851C-0010A4E62BB0}')! !Base64MimeConverter categoriesForClass!Unclassified! ! !Base64MimeConverter methodsFor! mimeDecode "Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full byte stream of characters. Reutrn a whole stream for the user to read." | nibA nibB nibC nibD | [mimeStream atEnd] whileFalse: [ (nibA := self nextValue) ifNil: [^ dataStream]. (nibB := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)) asCharacter. nibB := nibB bitAnd: 16rF. (nibC := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)) asCharacter. nibC := nibC bitAnd: 16r3. (nibD := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibC bitShift: 6) + nibD) asCharacter. ]. ^ dataStream! mimeDecodeToByteArray "Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full ByteArray of 0-255 values. Reutrn a whole stream for the user to read." | nibA nibB nibC nibD | [mimeStream atEnd] whileFalse: [ (nibA := self nextValue) ifNil: [^ dataStream]. (nibB := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)). nibB := nibB bitAnd: 16rF. (nibC := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)). nibC := nibC bitAnd: 16r3. (nibD := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibC bitShift: 6) + nibD). ]. ^ dataStream ! mimeEncode "Convert from data to 6 bit characters. changed to check for end of stream a bit more often like when it reads a character!! crCounter inserts CR's into stream to break up mime into reasonable length lines." | phase1 phase2 raw nib crCounter | phase1 := phase2 := false. crCounter := 0. [dataStream atEnd] whileFalse: [ crCounter := crCounter + 1. (crCounter > 80) ifTrue: [ mimeStream nextPutAll: #[ 13 10 ]. crCounter :=0 ]. raw := dataStream next asInteger. data := raw. nib := (data bitAnd: 16rFC) bitShift: -2. mimeStream nextPut: (ToCharTable at: nib+1). (dataStream atEnd) ifFalse: [ (raw := dataStream next)] ifTrue: [raw := 0. phase1 := true] . data := ((data bitAnd: 3) bitShift: 8) + raw asInteger. nib := (data bitAnd: 16r3F0) bitShift: -4. mimeStream nextPut: (ToCharTable at: nib+1). (dataStream atEnd) ifFalse: [(raw := dataStream next)] ifTrue: [raw := 0. phase2 := true]. data := ((data bitAnd: 16rF) bitShift: 8) + (raw asInteger). nib := (data bitAnd: 16rFC0) bitShift: -6. mimeStream nextPut: (ToCharTable at: nib+1). nib := (data bitAnd: 16r3F). mimeStream nextPut: (ToCharTable at: nib+1)]. phase1 ifTrue: [mimeStream skip: -2; nextPut: $=; nextPut: $=. ^ mimeStream]. phase2 ifTrue: [mimeStream skip: -1; nextPut: $=. ^ mimeStream]. ! nextValue "The next six bits of data char from the mimeStream, or nil. Skip all other chars" | raw num | [raw := mimeStream next. raw ifNil: [^ nil]. mimeStream atEnd ifTrue: [ ^nil]. raw == $= ifTrue: [^ nil]. num := FromCharTable at: raw asciiValue + 1. num ifNotNil: [^ num]. "else ignore space, return, tab, ..." true] whileTrue. ! ! !Base64MimeConverter categoriesFor: #mimeDecode!*-unclassified!public! ! !Base64MimeConverter categoriesFor: #mimeDecodeToByteArray!*-unclassified!public! ! !Base64MimeConverter categoriesFor: #mimeEncode!*-unclassified!public! ! !Base64MimeConverter categoriesFor: #nextValue!*-unclassified!public! ! !Base64MimeConverter class methodsFor! decodeInteger: mimeString | bytes sum | "Decode the MIME string into an integer of any length" bytes := (Base64MimeConverter mimeDecodeToBytes: (ReadStream on: mimeString)) contents. sum := 0. bytes reverseDo: [:by | sum := sum * 256 + by]. ^ sum ! encodeInteger: int | strm | "Encode an integer of any length and return the MIME string" strm := RWBinaryOrTextStream on: (ByteArray new: int basicSize+4). strm reset. 1 to: int basicSize do: [:ii | strm nextPut: (int byteAt: ii)]. strm reset. " added this AR" ^ ((self mimeEncode: strm) contents) copyUpTo: $= "remove padding" ! example "Base64MimeConverter example" "This example at least works!!" | ss bb | ss := RWBinaryOrTextStream on: (String new: 10). ss nextPutAll: 'Hi There!!!!'. bb := Base64MimeConverter mimeEncode: ss. "bb contents 'SGkgVGhlcmUh'" ^ (Base64MimeConverter mimeDecodeToChars: bb) contents ! initialize FromCharTable := Array new: 256. "nils" ToCharTable := Array new: 64. ($A asciiValue to: $Z asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind-1. ToCharTable at: ind put: val asCharacter]. ($a asciiValue to: $z asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind+25. ToCharTable at: ind+26 put: val asCharacter]. ($0 asciiValue to: $9 asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind+25+26. ToCharTable at: ind+26+26 put: val asCharacter]. FromCharTable at: $+ asciiValue + 1 put: 62. ToCharTable at: 63 put: $+. FromCharTable at: $/ asciiValue + 1 put: 63. ToCharTable at: 64 put: $/. ! mimeDecodeToBytes: aStream "Return a RWBinaryOrTextStream of the original ByteArray. aStream has only 65 innocuous character values. aStream is not binary. (See class comment). 4 bytes in aStream goes to 3 bytes in output." | me | aStream position: 0. me := self new mimeStream: aStream. me dataStream: (RWBinaryOrTextStream on: (ByteArray new: aStream size * 3 // 4)). me mimeStream reset. "added these AR" me dataStream reset. me mimeDecodeToByteArray. me dataStream position: 0. ^ me dataStream ! mimeDecodeToChars: aStream "Return a ReadWriteStream of the original String. aStream has only 65 innocuous character values. It is not binary. (See class comment). 4 bytes in aStream goes to 3 bytes in output." | me | aStream position: 0. me := self new mimeStream: aStream. me dataStream: (RWBinaryOrTextStream on: (String new: aStream size * 3 // 4)). me mimeStream reset. me dataStream reset. me mimeDecode. me dataStream position: 0. ^ me dataStream ! mimeEncode: aStream "Return a ReadWriteStream of characters. The data of aStream is encoded as 65 innocuous characters. (See class comment). 3 bytes in aStream goes to 4 bytes in output." | me | me := self new dataStream: aStream. me mimeStream: (RWBinaryOrTextStream on: (String new: aStream size + 20 * 4 // 3)). me mimeStream reset. me dataStream reset. me mimeEncode. me mimeStream position: 0. ^ me mimeStream ! ! !Base64MimeConverter class categoriesFor: #decodeInteger:!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #encodeInteger:!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #example!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #initialize!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #mimeDecodeToBytes:!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #mimeDecodeToChars:!*-unclassified!public! ! !Base64MimeConverter class categoriesFor: #mimeEncode:!*-unclassified!public! ! RWBinaryOrTextStream comment: 'From squeak, simulation in memory of a FileStream A simulation of a FileStream, but living totally in memory. Hold the contents of a file or web page from the network. Can then fileIn like a normal FileStream. Need to be able to switch between binary and text, as a FileStream does, without recopying the whole collection. Convert to binary upon input and output. Always keep as text internally. Problems: does not work well with event like end of file. Does not initialize well. Eg, when does isBinary get set.'! RWBinaryOrTextStream guid: (GUID fromString: '{C18C60D2-DEF7-11D4-851C-0010A4E62BB0}')! !RWBinaryOrTextStream categoriesForClass!Unclassified! ! !RWBinaryOrTextStream methodsFor! asBinaryOrTextStream ^self.! ascii isBinary:=false.! binary isBinary:=true.! contents "copy of myself from 1..readLimit." | newArray | isBinary ifFalse: [^super contents]. readLimit := readLimit max: position. newArray := ByteArray new: readLimit. ^newArray replaceFrom: 1 to: readLimit with: collection startingAt: 1. ! contentsOfEntireFile ^self contents! isBinary ^isBinary.! next | byte | self atEnd ifTrue: [ ^0 ]. " avoid error signal on read beyond end." ^ isBinary ifTrue: [byte := super next. byte ifNil: [nil] ifNotNil: [byte asciiValue]] ifFalse: [super next]. ! next: anInteger "Answer the next anInteger elements of my collection. Must override to get class right." | newArray | newArray := (isBinary ifTrue: [ByteArray] ifFalse: [String]) new: anInteger. ^ self nextInto: newArray.! nextPut: charOrByte super nextPut: charOrByte asCharacter! on: aCollection super on: aCollection. self reset.! padToEndWith: aChar "We don't have pages, so we are at the end, and don't need to pad." ! reset "Set the receiver's position to the beginning of the sequence of objects." "you should always reset this after creating it." super reset. isBinary ifNil: [isBinary := false]. collection class == ByteArray ifTrue: ["Store as String and convert as needed." collection := collection asString. isBinary := true]. ! setFileTypeToObject "do nothing. We don't have a file type" ! text isBinary := false. ! ! !RWBinaryOrTextStream categoriesFor: #asBinaryOrTextStream!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #ascii!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #binary!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #contents!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #contentsOfEntireFile!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #isBinary!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #next!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #next:!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #nextPut:!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #on:!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #padToEndWith:!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #reset!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #setFileTypeToObject!*-unclassified!public! ! !RWBinaryOrTextStream categoriesFor: #text!*-unclassified!public! ! "Binary Globals"! "Resources"! |
In reply to this post by Chris Uppal-2
"Chris Uppal" <[hidden email]> wrote in message
news:[hidden email]... [...] > to refuse SMTP connections from IP addresses which haven't successfully done > a POP3 (or similar) login in the previous <n> minutes. I *suspect* that > your ISP is using something similar, or how else could an ordinary > brain-damaged client like M$ Outlook (spit!) send email at all. My (probably deficient) understanding was that Outlook, et al., use POP3 or IMAP4 to send and receive e-mail. Those allow the server to authenticate users before anything really interesting happens. [...] > Come to think of it, there's no reason why an SMTP server should accept > incoming connections, even if they *are* going to submit email for > subdomains it "owns". That too is a standing invitation to spam. I guess [...] I think SMTP servers have to accept incoming connections, since (I think) that's the only way for mail to move from domain to domain. For example, our Exchange server has to talk SMTP to be able to send mail to non-Exchange servers. When we send a message to anyone outside our organization, the server looks up the MX records for that domain, and then tries to establish an SMTP connection to one of those hosts, in order of preference (as identified by the "cost" field in the DNS record). Consequently, for my purposes at least, some way of retrieving MX records, since the SMTP stuff is pleasantly straightforward. I think you can issue DNS requests via TCP/IP (DNS servers are supposed to support both TCP/IP and UDP connections), but I haven't been successful at it yet. I may actually have to take a glance at the specs (horrors!). Don |
In reply to this post by alban read
Alban,
"alban read" <[hidden email]> wrote in message news:1vTp6.3390$[hidden email]... > Here is a simple SMTP classs. The clever parts are from Squeak. > The bits I wrote do work but are not pretty. Its not finished yet. [...] The MIME stuff looks like it could be really handy. In my spare time, though, I'm still looking at how to get MX records from a DNS server. Host address records are no problem from within Dolphin, since the Sockets Connection has everything you need for that. I was just hoping that Winsock would be more help in retrieving MX records, too. Oh, well... Don |
In reply to this post by Don Rylander
"Don Rylander" <[hidden email]> wrote in
<98ars4$18ivq$[hidden email]>: >My (probably deficient) understanding was that Outlook, et al., use POP3 >or IMAP4 to send and receive e-mail. Those allow the server to >authenticate users before anything really interesting happens. POP3 doesn't do sending mail, just reading it. I believe the same is true for IMAP4. If you examine the relevant dialogs in Outlook, you'll see a setting for the SMTP server for sending mail. P. |
"Paul Hudson" <[hidden email]> wrote in message
news:Xns90606EA1DED61phudsonpoboxcom@127.0.0.1... > "Don Rylander" <[hidden email]> wrote in > <98ars4$18ivq$[hidden email]>: > > >My (probably deficient) understanding was that Outlook, et al., use POP3 > >or IMAP4 to send and receive e-mail. Those allow the server to > >authenticate users before anything really interesting happens. > > POP3 doesn't do sending mail, just reading it. I believe the same is true > for IMAP4. > > If you examine the relevant dialogs in Outlook, you'll see a setting for > the SMTP server for sending mail. I guess I should have said definitely deficient. Indeed, Outlook Express and Outlook (in its Internet mail configuration) both use SMTP. Now I have a better understanding of Chris' comment about how different mail servers authenticate senders. Of course, even a brain-dead client like Outlook can send SMTP if it doesn't have to find the server. > > P. Don |
In reply to this post by Paul Hudson
Paul Hudson wrote:
> POP3 doesn't do sending mail, just reading it. I believe the same is true > for IMAP4. You've said it for me, Paul. I just wanted to add that a very good (in my opinion) book on internet email protocols is: Internet Email Protocols A Developer's Guide Kevin Johnson ISBN: 0-201-43288-9 It's only about internet stuff -- it doesn't touch x.400 (and why should it?). Also it's about protocols, not tools (so there's nothing on sendmail configuration, say). But is does go into lots of useful and illuminating detail on the protocols, and discusses the relationships between the various relevant RFCs. The only problem is that it's impossible to read without being tempted to implement your own email suite... -- chris |
Free forum by Nabble | Edit this page |