Skip to content

Commit

Permalink
Move methods to extension packages.
Browse files Browse the repository at this point in the history
  • Loading branch information
James Foster committed Jul 23, 2019
1 parent 7e2b180 commit 8b677a9
Show file tree
Hide file tree
Showing 6 changed files with 46 additions and 47 deletions.
14 changes: 14 additions & 0 deletions src/Graphics-Files/ZnEasy.extension.st
@@ -0,0 +1,14 @@
Extension { #name : #ZnEasy }

{ #category : #'*Graphics-Files' }
ZnEasy class >> getImageOfType: mimeType fromUrl: urlObject [
| client |
(client := self client)
url: urlObject;
accept: mimeType;
enforceHttpSuccess: true;
enforceAcceptContentType: true;
get.
"ImageReadWriter does automatic type detection"
^ ImageReadWriter formFromStream: client entity readStream
]
21 changes: 0 additions & 21 deletions src/Network-MIME/MIMEDocument.class.st
Expand Up @@ -260,27 +260,6 @@ MIMEDocument >> mimeType [
^type
]

{ #category : #accessing }
MIMEDocument >> parts [
"Return the parts of this message. There is a far more reliable implementation of parts in MailMessage, but for now we are continuing to use this implementation"
| parseStream currLine separator msgStream messages |
self isMultipart ifFalse:
[ ^ #() ].
parseStream := self content readStream.
currLine := ''.
[ '--*' match: currLine ] whileFalse: [ currLine := parseStream nextLine ].
separator := currLine copy.
msgStream := LimitingLineStreamWrapper
on: parseStream
delimiter: separator.
messages := OrderedCollection new.
[ parseStream atEnd ] whileFalse:
[ messages add: msgStream upToEnd.
msgStream skipThisLine ].
"MailMessage is not present in a minimal image"
^ messages collect: [ :e | (self environment at: #MailMessage) from: e ]
]

{ #category : #printing }
MIMEDocument >> printOn: aStream [
aStream nextPutAll: self class name;
Expand Down
21 changes: 21 additions & 0 deletions src/Network-Mail/MIMEDocument.extension.st
@@ -0,0 +1,21 @@
Extension { #name : #MIMEDocument }

{ #category : #'*Network-Mail' }
MIMEDocument >> parts [
"Return the parts of this message. There is a far more reliable implementation of parts in MailMessage, but for now we are continuing to use this implementation"
| parseStream currLine separator msgStream messages |
self isMultipart ifFalse:
[ ^ #() ].
parseStream := self content readStream.
currLine := ''.
[ '--*' match: currLine ] whileFalse: [ currLine := parseStream nextLine ].
separator := currLine copy.
msgStream := LimitingLineStreamWrapper
on: parseStream
delimiter: separator.
messages := OrderedCollection new.
[ parseStream atEnd ] whileFalse:
[ messages add: msgStream upToEnd.
msgStream skipThisLine ].
^ messages collect: [ :e | MailMessage from: e ]
]
11 changes: 11 additions & 0 deletions src/Network-Mail/SMTPClient.extension.st
Expand Up @@ -6,3 +6,14 @@ SMTPClient class >> deliver: aMailMessage usingServer: aString [

self deliverMailFrom: aMailMessage from to: aMailMessage recipientList text: aMailMessage text usingServer: aString.
]

{ #category : #'*Network-Mail' }
SMTPClient >> mailFrom: fromAddress [
" MAIL <SP> FROM:<reverse-path> <CRLF>"

| address |
address := (MailAddressParser addressesIn: fromAddress) first.

self sendCommand: 'MAIL FROM: <', address, '>'.
self checkResponse.
]
12 changes: 0 additions & 12 deletions src/Network-Protocols/SMTPClient.class.st
Expand Up @@ -154,18 +154,6 @@ SMTPClient >> login [
self checkResponse
]

{ #category : #'private protocol' }
SMTPClient >> mailFrom: fromAddress [
" MAIL <SP> FROM:<reverse-path> <CRLF>"

| address |
"MailAddressParser is not in the minimal image"
address := ((self environment at: #MailAddressParser) addressesIn: fromAddress) first.

self sendCommand: 'MAIL FROM: <', address, '>'.
self checkResponse.
]

{ #category : #'public protocol' }
SMTPClient >> mailFrom: sender to: recipientList text: messageText [
"deliver this mail to a list of users. NOTE: the recipient list should be a collection of simple internet style addresses -- no '<>' or '()' stuff"
Expand Down
14 changes: 0 additions & 14 deletions src/Zinc-HTTP/ZnEasy.class.st
Expand Up @@ -76,20 +76,6 @@ ZnEasy class >> getGif: urlObject [
fromUrl: urlObject
]

{ #category : #private }
ZnEasy class >> getImageOfType: mimeType fromUrl: urlObject [
| client |
(client := self client)
url: urlObject;
accept: mimeType;
enforceHttpSuccess: true;
enforceAcceptContentType: true;
get.
"ImageReadWriter does automatic type detection"
"ImageReadWriter is not in minimal image"
^ (self environment at: #ImageReadWriter) formFromStream: client entity readStream
]

{ #category : #operations }
ZnEasy class >> getJpeg: urlObject [
"self getJpeg: 'http://stfx.eu/sun-fire-x2100.jpg'."
Expand Down

0 comments on commit 8b677a9

Please sign in to comment.