Consulting

Results 1 to 4 of 4

Thread: Excel and Outlook Global Address List

  1. #1

    Excel and Outlook Global Address List

    Hello

    I have a userform and in one box I need to type in a user name

    Now with outlook on our system here, in the To: Field if you type in the user name and click check names it will bring up the user's full name

    In my Txtbox is there a way as soon as I type in the username it automatically checks the global address book and will automatically prefill what i've put in with the users full name?

    I seem to be asking a lot of questions tonight lol but have still to find a limitation to what I can do with VBA lol

  2. #2
    Site Admin
    Urban Myth
    VBAX Guru
    Joined
    May 2004
    Location
    Oregon, United States
    Posts
    4,940
    Location
    Hi there,

    Not really. If you could (I'm sure there is a way) it would probably be gawd awful slow and very inefficient. The list you're referring to isn't even a Contact list, it is only a list of recently used items typed in that field. And each Outlook form has it's own unique list for each unique field. In other words, you can have a lot of these lists with very different items in each. I've often heard people calling these lists 'my contact list', which it is most definitely not. I had one guy tell me he had all of his contacts at his fingertips and never - never - used the actual Contacts list in Outlook. Well, he had to reinstall in lieu of issues, then asked, "where are all my contacts?!" Just ludacris.

    You could however pre-populate a drop down with these contacts. Take a look here to see an example of accessing the GAL in Outlook.

    HTH

  3. #3
    Hmmmmm seem to get some Syntax errors with some code in 'Array'

    Have checked and my system is running XL 2003

    By the way My GAL (at the office) contains a good couple of THOUSAND contacts - If I was to be successful at some point to getting this working will this crash the Mail Server or will Office just simply hang?

    I'm anticipating it would take about an hour to populate the info, maybe more lol

  4. #4
    Site Admin
    Urban Myth
    VBAX Guru
    Joined
    May 2004
    Location
    Oregon, United States
    Posts
    4,940
    Location
    For me, this gets all of my GAL into a new worksheet...

    [vba]Sub GetGAL()
    Dim wb As Workbook, ws As Worksheet
    Dim blnCreated As Boolean, iCnt As Long
    Dim objApp As Object, objSession As Object, oFolder As Object
    Set objApp = GetObject(, "Outlook.Application")
    blnCreated = False
    If objApp Is Nothing Then
    Set objApp = CreateObject("Outlook.Application")
    blnCreated = True
    End If
    Set objSession = objApp.GetNamespace("MAPI")
    objSession.Logon
    objSession.Logon , , False, False ' Profile, Password, ShowDialog, NewSession
    Set oFolder = objSession.AddressLists("Global Address List")
    On Error Resume Next
    'Some fields may not exist
    'Turn off screen updating
    Call ToggleEvents(False)
    Set wb = Workbooks.Add(xlWorksheet)
    Set ws = wb.Sheets(1)
    For iCnt = 1 To oFolder.AddressEntries.Count
    ws.Cells(iCnt + 1, 1).Value = oFolder.AddressEntries(iCnt)
    Next iCnt
    ws.Cells(1, 1).Value = "GAL Entries"
    ws.Cells(1, 1).Font.Bold = True
    ws.Columns(1).EntireColumn.AutoFit
    Call ToggleEvents(True)
    If blnCreated = True Then objApp.Quit
    End Sub

    Sub ToggleEvents(blnState As Boolean)
    'Originally written by firefytr
    With Application
    .DisplayAlerts = blnState
    .EnableEvents = blnState
    .ScreenUpdating = blnState
    If blnState Then .CutCopyMode = False
    If blnState Then .StatusBar = False
    End With
    End Sub[/vba]

    Is that what you're looking for? If so, put that in your initialize event and instead of writing to a workbook, write to your combobox.

    HTH

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •