Email from excel with outlook..code win00 XL00


Posted by Dave on November 25, 2001 11:53 AM

How's everyone doing. I've pieced together some code to email a recipient if the name is in outlook contacts.In the body of the email I would like to show items needed from cells c1 to c6 (more cells will be added later all in column c) THE PROBLEM is that cells c1 to c6 will not be the same all the time there is an if condition attached such as =IF(A5<>0,"","need address information"). So sometimes there will be blank cells in the c column. If anyone can help me format the body of the email so not to include blanks and look nice and pretty I would greatly be thankful. I tried using a string and range but it proved difficult.

Sub Send_Msg2()
Dim objOL As New Outlook.Application
Dim objMail As MailItem
Dim Fname As String
Dim string1 As String
Set objOL = New Outlook.Application
Set objMail = objOL.CreateItem(olMailItem)
Recipient = Range("a11") 'email recipient name in cell
Fname = Left(Worksheets(1).Range("A11").Value, InStr(1, Worksheets(1).Range("A11").Value, " ") - 1)

Application.StatusBar = "Compiling email.....hang on!"
With objMail

.To = Recipient
.CC = "boss@boss.com"
.Subject = "Items needed for valuation"
.Body = Fname & "," & Chr(13) & Chr(13) & _
"If possible could the folling items be supplied." & Chr(13) & Chr(13) & _
Range("c2") & vbCrLf _
& Range("c3") & vbCrLf _
& Range("c4") & vbCrLf _
& Range("c5") & vbCrLf _
& Range("c6") & vbCrLf & Chr(13) & Chr(13) & _
"Thank You," & Chr(13) & Chr(13) & _
"David Duques"
.Attachments.Add ("c:\My Documents\book3.xls")
.Display
End With
Application.StatusBar = False

Set objMail = Nothing
Set objOL = Nothing
End Sub


TIA
David Duques
www.gulfcoastfinancial.com
888.893.1803

Posted by Bariloche on November 25, 2001 12:48 PM

Dave,

If I understand your problem correctly I'd suggest that you compose the text of the body of your e-mail separately and then insert that in your e-mail text.

Use this code line to find the last cell used in column C:

LastRow = Cells(65536, 3).End(xlUp).Row

Then just loop through the cells in column C to create your list:

EvalListMsg = "If possible could the following items be supplied." & Chr(13) & Chr(13)

For i = 2 to LastRow

EvalListMsg = EvalListMsg & Cells(i,3).Value & Chr(13)

Next i


Then just insert the variable "EvalListMsg" into your e-mail text.

Some variant of this approach should work. You may have to play around with the Chr(13)s to get the formatting right but the basic idea should be what you need.


Hope this helps, good luck.

.To = Recipient .CC = "boss@boss.com" .Subject = "Items needed for valuation" .Body = Fname & "," & Chr(13) & Chr(13) & _ "If possible could the folling items be supplied." & Chr(13) & Chr(13) & _ Range("c2") & vbCrLf _ & Range("c3") & vbCrLf _ & Range("c4") & vbCrLf _ & Range("c5") & vbCrLf _ & Range("c6") & vbCrLf & Chr(13) & Chr(13) & _ "Thank You," & Chr(13) & Chr(13) & _ "David Duques" .Attachments.Add ("c:\My Documents\book3.xls") .Display

Posted by Dave on November 25, 2001 1:43 PM

Thaks alot for the input, your code works perfectly and makes the insertion of the items in the body much easier and cleaner. I still run into the problem of blank(no value) cells apearing in the body. As an example if there are 3 items in row c with the formula
C1=IF(A5<>0,"","need address information")
C2=IF(A6<>0,"","need owners name")
C3=IF(A7<>0,"","need tax returns")

Let's say the first and last items are needed then column c will look like and so will email

need address information

need tax returns

BUT I want the body of the E-mail to look like

need address information
need tax returns

This is because there could be 20 to 30 items and it will look better.

TIA
DAVE Dave, If I understand your problem correctly I'd suggest that you compose the text of the body of your e-mail separately and then insert that in your e-mail text. Use this code line to find the last cell used in column C: LastRow = Cells(65536, 3).End(xlUp).Row Then just loop through the cells in column C to create your list: EvalListMsg = "If possible could the following items be supplied." & Chr(13) & Chr(13) For i = 2 to LastRow EvalListMsg = EvalListMsg & Cells(i,3).Value & Chr(13) Next i

.To = Recipient .CC = "boss@boss.com" .Subject = "Items needed for valuation" .Body = Fname & "," & Chr(13) & Chr(13) & _ "If possible could the folling items be supplied." & Chr(13) & Chr(13) & _ Range("c2") & vbCrLf _ & Range("c3") & vbCrLf _ & Range("c4") & vbCrLf _ & Range("c5") & vbCrLf _ & Range("c6") & vbCrLf & Chr(13) & Chr(13) & _ "Thank You," & Chr(13) & Chr(13) & _ "David Duques" .Attachments.Add ("c:\My Documents\book3.xls") .Display

Posted by Dave on November 25, 2001 1:48 PM

Re: Email from exc.....Appened Code

Sub Send_Msg3()
Dim objOL As New Outlook.Application
Dim objMail As MailItem
Dim Fname As String

Set objOL = New Outlook.Application
Set objMail = objOL.CreateItem(olMailItem)
Recipient = Range("a11") 'email recipient name in cell
Fname = Left(Worksheets("a").Range("A11").Value, InStr(1, Worksheets("a").Range("A11").Value, " ") - 1)

LastRow = Cells(65536, 3).End(xlUp).Row
EvalListMsg = "If possible could the following items be supplied." & Chr(13) & Chr(13)
For i = 2 To LastRow
EvalListMsg = EvalListMsg & Cells(i, 3).Value & Chr(13)
Next i


Application.StatusBar = "Compiling email.....hang on!"
With objMail

.To = Recipient
'.CC = "boss@boss.com"
.Subject = "Items needed for valuation"
.Body = Fname & "," & Chr(13) & Chr(13) & _
EvalListMsg & Chr(13) & Chr(13) & _
"Thank You," & Chr(13) & Chr(13) & _
"David Duques"
'.Attachments.Add ("c:\My Documents\book3.xls")
.Display
End With
Application.StatusBar = False

Set objMail = Nothing
Set objOL = Nothing
End Sub Thaks alot for the input, your code works perfectly and makes the insertion of the items in the body much easier and cleaner. I still run into the problem of blank(no value) cells apearing in the body. As an example if there are 3 items in row c with the formula .To = Recipient .CC = "boss@boss.com" .Subject = "Items needed for valuation" .Body = Fname & "," & Chr(13) & Chr(13) & _ "If possible could the folling items be supplied." & Chr(13) & Chr(13) & _ Range("c2") & vbCrLf _ & Range("c3") & vbCrLf _ & Range("c4") & vbCrLf _ & Range("c5") & vbCrLf _ & Range("c6") & vbCrLf & Chr(13) & Chr(13) & _ "Thank You," & Chr(13) & Chr(13) & _ "David Duques" .Attachments.Add ("c:\My Documents\book3.xls") .Display

Posted by Dave on November 25, 2001 2:06 PM

BTW how to put range in body like A1:d10? TIA

Posted by Bariloche on November 25, 2001 4:42 PM

Re: Email from exc.....Appened Code

Dave,

Just test for a zero-length string before using the contents of the cell. This would look like:


For i = 2 To LastRow

If Cells(i,3).Value <> "" Then
EvalListMsg = EvalListMsg & Cells(i, 3).Value & Chr(13)
End If
Next i

Also, you probably should dimension the new variables. I'd recommend:

Dim LastRow as Double
Dim i as Double
Dim EvalListMsg as String


Sorry, but I don't have any suggestions for copying the range data and pasting it in the e-mail. I don't know what the syntax is for calling something off the clip board. Perhaps someone else can enlighten us. :-)


take care

Posted by Bariloche on November 25, 2001 5:07 PM

Dave,

You may also want to check out this article. I haven't read it yet, but it could have some useful info.


http://www.microsoft.com/exceldev/articles/bulkmail.htm



Posted by Dave on November 25, 2001 5:15 PM

Thanks it's perfect...much appreciated!

Just test for a zero-length string before using the contents of the cell. This would look like: