[AccessD] Opening Outlook if closed code not working

Dan Waters dwaters at usinternet.com
Thu Mar 13 17:03:00 CST 2003


Doris,

I'll try out your code this weekend - Thanks for posting it!  

In the meantime, what is Redemption?  Is this an email program/utility
that can be downloaded?  I did a google search and got many religious
references . . .  This sounds like it would be great to use when doing
laptop demos!

Thanks,
Dan Waters


-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of Mike and Doris
Manning
Sent: Thursday, March 13, 2003 3:33 PM
To: accessd at databaseadvisors.com
Subject: RE: [AccessD] Opening Outlook if closed code not working


The problem with shelling out to a program is that control doesn't pass
back to the calling program until the shelled out program closes.  That
is why I asked you what you needed to do with Outlook that you couldn't
do via VBA.

In my code I pass the bolOutlook variable back to the calling routine
via the function so that when I'm done working with Outlook, I know
whether I need to shut it down or not.  Here is the code that calls the
function I sent you earlier (uses Redemption to bypass Outlook
Security):

Public Function SendSafeEmail(SendTo As String, SendSubj As String, _
                     SendBody As String, SendEdit As Boolean, _
                     Optional SendCC As String)
                                         
    On Error GoTo ErrorHandler
    
    Dim oMail As Object
    Dim oSpace As Object
    Dim oFoldr As Object
    Dim oItem As Object
    Dim oSafe As Object
    Dim oDeliver As Object
    Dim bolOpen As Boolean
    
    bolOpen = IsOutlookOpen
    
    Set oMail = CreateObject("Outlook.Application")
    Set oSpace = oMail.GetNamespace("MAPI")
    Set oFoldr = oSpace.GetDefaultFolder(olFolderOutbox)
    Set oItem = oMail.CreateItem(olMailItem)
    Set oSafe = CreateObject("Redemption.SafeMailItem")
    oSafe.Item = oItem

    With oSafe
        .Recipients.Add SendTo
        If IsMissing(SendCC) = False Then .Recipients.Add SendCC
        .Recipients.ResolveAll
        .Subject = SendSubj
        .Body = SendBody
        If SendEdit = True Then
            .Display
        Else
            .Send
        End If
    End With
    
    Set oDeliver = CreateObject("Redemption.MAPIUtils")
    oDeliver.DeliverNow
    oDeliver.Cleanup
    
    If bolOpen = False Then
        oMail.Quit
    End If
    
    Set oDeliver = Nothing
    Set oSafe = Nothing
    Set oItem = Nothing
    Set oFoldr = Nothing
    Set oSpace = Nothing
    Set oMail = Nothing

    Exit Function
    
ErrorHandler:
    Call HandleErrors(Err, strMyName, "SendSafeEmail")
    
End Function

Doris Manning
Database Administrator
Hargrove Inc.
www.hargroveinc.com



-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of Dan Waters
Sent: Thursday, March 13, 2003 03:53 PM
To: accessd at databaseadvisors.com
Subject: RE: [AccessD] Opening Outlook if closed code not working


Doris,

The problem I had with using CreateObject was that Outlook closed when
the object variable went out of scope, or when Access was closed.

Opening Outlook using Shell will open Outlook so that it will stay open,
but upon opening the Outlook window becomes Active instead of the Access
window.

Is there a way out of this dilemma?

Thanks,
Dan Waters


-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of
paul.hartland at fsmail.net
Sent: Wednesday, March 12, 2003 8:31 AM
To: accessd at databaseadvisors.com
Subject: RE: RE: [AccessD] Opening Outlook if closed code not working


Thanks so much, don't know what I would do without this list at
times......


From: "Mike and Doris Manning" <mikedorism at ntelos.net>
Date: Wed 12/Mar/2003 14:31 GMT
To: <accessd at databaseadvisors.com>
Subject: RE: RE: [AccessD] Opening Outlook if closed code not working

What you need to do is create a reference to the Outlook Object Model.
Here are some websites that will give you most of the info you need to
know.

www.outlookexchange.com/articles/home/outlookobjectmodel.asp
www.microsoft.com/office/previous/outlook/SuprEasy.asp 
www.microsoft.com/mind/0597/outlook.asp

Doris Manning
Database Administrator
Hargrove Inc.
www.hargroveinc.com


-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of
paul.hartland at fsmail.net
Sent: Wednesday, March 12, 2003 08:39 AM
To: accessd at databaseadvisors.com
Subject: RE: RE: [AccessD] Opening Outlook if closed code not working


Basically, I just want to open Outlook if it's closed then return the
focus to my application......Unfortunately I don't know how to open
Outlook any other way using Visual Basic 6 apart from shelling out.....

Could you point me in the right direction to opening Outlook using
Visual Basic 6 ?

Thanks in advance.....

Paul


From: "Mike and Doris Manning" <mikedorism at ntelos.net>
Date: Wed 12/Mar/2003 13:30 GMT
To: <accessd at databaseadvisors.com>
Subject: RE: RE: [AccessD] Opening Outlook if closed code not working

Why are you shelling out to it?  What are you trying to do with Outlook
that you can't do via VBA code?

Doris Manning
Database Administrator
Hargrove Inc.
www.hargroveinc.com


-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of
paul.hartland at fsmail.net
Sent: Wednesday, March 12, 2003 04:57 AM
To: accessd at databaseadvisors.com
Subject: Re: RE: [AccessD] Opening Outlook if closed code not working


Thanks, works like a dream........But do you know a way around my next
problem.....

I use Shell("D:\Program Files\Microsoft
Office\Office\Outlook.exe",vbMinimizedNoFocus)  now although this opens
Outlook, Outlook retains the focus, and my application is hidden behind
it. Is there a way I can tell Outlook to open and then return the focus
to my application ?

Thanks in advance......

Paul Hartland


From: "Mike and Doris Manning" <mikedorism at ntelos.net>
Date: Tue 11/Mar/2003 16:20 GMT
To: <accessd at databaseadvisors.com>
Subject: RE: [AccessD] Opening Outlook if closed code not working

I ran into the same problem.  Here is the code from my IsOutlookOpen
module:

Option Compare Database
Option Explicit

Private bolOutlook As Boolean

Declare Function GetClassName Lib "user32" Alias "GetClassNameA" _
    (ByVal hwnd As Long, ByVal lpClassName As String, _
    ByVal nMaxCount As Long) As Long

Declare Function GetWindowTextLength Lib "user32" _
    Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long

Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" _
    (ByVal hwnd As Long, ByVal lpString As String, _
    ByVal CCh As Long) As Long

Declare Function EnumWindows Lib "user32" _
    (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

Declare Function FindWindow Lib "user32" Alias "FindWindowA" _
    (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Public Function IsOutlookOpen() As Boolean
' This is the entry point that makes it happen
    EnumWindows AddressOf EnumWindowProc, 0
    IsOutlookOpen = bolOutlook
End Function

Public Function EnumWindowProc(ByVal hwnd As Long, _
    ByVal lParam As Long) As Long

    'Do stuff here with hwnd
    Dim sClass As String
    Dim sIDType As String
    Dim sTitle As String
    
    'Get the title to the window
    sTitle = GetWindowIdentification(hwnd, sIDType, sClass)
    
    'Check to see if it is an Outlook window
    If InStr(1, sTitle, "Microsoft Outlook") > 0 Then
        bolOutlook = True
        EnumWindowProc = False
    Else
        bolOutlook = False
        EnumWindowProc = True
    End If
End Function

Private Function GetWindowIdentification(ByVal hwnd As Long, _
  sIDType As String, sClass As String) As String

    Dim nSize As Long
    Dim sTitle As String
    
    'get the size of the string required
    'to hold the window title
    nSize = GetWindowTextLength(hwnd)
    
    'if the return is 0, there is no title
    If nSize > 0 Then
        sTitle = Space$(nSize + 1)
        Call GetWindowText(hwnd, sTitle, nSize + 1)
        sIDType = "title"
        sClass = Space$(64)
        Call GetClassName(hwnd, sClass, 64)
    Else
        'no title, so get the class name instead
        sTitle = Space$(64)
        Call GetClassName(hwnd, sTitle, 64)
        sClass = sTitle
        sIDType = "class"
    End If
    
    GetWindowIdentification = TrimNull(sTitle)
End Function

Private Function TrimNull(StartStr As String) As String
    Dim Pos As Integer
    
    Pos = InStr(StartStr, Chr$(0))
    If Pos Then
        TrimNull = LEFT(StartStr, Pos - 1)
        Exit Function
    End If
    
    'if this far, there was
    'no Chr$(0), so return the string
    TrimNull = StartStr
End Function

Doris Manning
Database Administrator
Hargrove Inc.
www.hargroveinc.com


-----Original Message-----
From: accessd-admin at databaseadvisors.com
[mailto:accessd-admin at databaseadvisors.com] On Behalf Of
paul.hartland at fsmail.net
Sent: Tuesday, March 11, 2003 09:22 AM
To: accessd at databaseadvisors.com; dba-vb at databaseadvisors.com
Subject: [AccessD] Opening Outlook if closed code not working


To all,

Can anyone see why the following code (VB6) would open Outlook even if
it is already open, I want a module that when I run my application, it
checks to see if Outlook is open if not open it......

Function OpenOutlook()
    Dim objOut As Object
    On Error Resume Next
    
    Set objOut = GetObject("Outlook.Application")
    
    If (Err <> 0) Then
        Dim strOpenOutlook
        strOpenOutlook = Shell("D:\PROGRAM FILES\MICROSOFT
OFFICE\OFFICE\OUTLOOK.EXE", vbMinimizedNoFocus)
    End If
End Function

Thanks in advance.

Paul

_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com


________________________________________________________________________
__
Freeserve AnyTime - Go online whenever you want for just £6.99 a month
for your first 3 months, that's HALF PRICE! And then it's just £13.99 a
month after that.

For more information visit http://www.freeserve.com/time/ or call free
on 
0800 970 8890


_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com

_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com


________________________________________________________________________
__
Freeserve AnyTime - Go online whenever you want for just £6.99 a month
for your first 3 months, that's HALF PRICE! And then it's just £13.99 a
month after that.

For more information visit http://www.freeserve.com/time/ or call free
on 
0800 970 8890


_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com

_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com


________________________________________________________________________
__
Freeserve AnyTime - Go online whenever you want for just £6.99 a month
for your first 3 months, that's HALF PRICE! And then it's just £13.99 a
month after that.

For more information visit http://www.freeserve.com/time/ or call free
on 
0800 970 8890


_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com


_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com

_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com





More information about the AccessD mailing list