Skip to content

Wireless


After digging to a depth of 100 meters last year, Russian scientists have found traces of copper wire dating back 1000 years, and came to the conclusion that their ancestors already had a telephone network one thousand years ago.

So, not to be outdone, in the weeks that followed, American scientists dug 200 meters and headlines in the US papers read: “US scientists have found traces of 2000 year old optical fibers, and have concluded that their ancestors already had advanced high-tech digital telephone 1000 years earlier than the Russians.”

One week later, the Singapore newspapers reported the following: “After digging as deep as 500 meters, Singapore scientists have found absolutely nothing. They
have concluded that 5000 years ago, their ancestors were already using wireless technology.

OpenNextContextTask


 

The macros and installation guides are stored in this this blog post

In outlook there is a nice feature to open the next email when one is read. To do so change the option as shown.

2

For my GTD setup, I would like to start doing a context task, for example @Computer and when I mark this task as complete, the next task listed lower and with the same context opens up.

3

To do so, I used some VBA codes to do so. This current version is crude but serve my purpose. After you install the VBA codes, press ALT-F8 and run the macro “NextContextTask” which is like an on/off switch.

Or you can add a button on the ribbon pointing to this macro. When you press it, it runs the macro and it turn on the feature, the next press will turn off the feature.

 

LIMITATION

 

Outlook 2010 does not allow the programmer to ‘see’ how the current user is looking at his task. It may be group by categories and sorted by Due date as shown above. However, in the @StoryBook  category, the 4 items are ordered using a property known as TodoTaskOrdinal.

For example, if you had a list of tasks 1,2,3, and you keep delaying completing task 2 by changing it’s startdate / duedate. When you add in new task 4,5,6 you may see 4,2,5,6 in your outlook view when you sort by Due date.

However, in the background, task 2 has a higher TodoTaskOrdinal because it was an ‘old’ task. If you look at the todo bar, the sequence of listed task is actually 2,4,5,6. Outlook ‘remember’ that you have been delaying task 2 and rank it higher.

So when you use this macro, sometime you will observe that it skip some obvious tasks and go to other task much lower or higher that the one you just closed. This is because the macro search and open the next task ranked by TodoTaskOrdinal .

At the current moment, it is difficult for one to ‘see’ the actual layout of what the user are looking at because of the XML mechanism Outlook 2010 has adopted. In the future when I have time, I’ll improve it.

Source Code for OpenNextContextTask


 

The purpose of these VBA codes is explained in this post

1

Important

There are 7 modules you need to import into your VBA editor. Guide to installation and notes on my programming

Info for programmers

Basically I setup event handlers for inspectors object and inspector object. I added some twist to enable more than one inspector object to have event handling capabilities.

These inspector objects are for taskitem so that when the user close the task or mark one as completed, it will open another task that has the same context AND one taskordinal below it (ie one task that was ranked next in line on the todo bar or task explorer).

Download

The source codes can be downloaded at my Public Skydrive folder. You can view the codes below, note if you copy and paste from this blog post, be aware some browsers will change the singlequote ‘ and doublequotes “” to something else and VBA editor will show as error. Just change them back after you copied into your outlook

 

ThisOutlookSession

 

Option Explicit

Private Sub Application_Startup()

‘——————————————————————————-

‘ Name      -   Application_Startup
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Start my EZGTD program when Outlook launch

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   None

‘ Return    -   None

‘ Reference -   See
https://ideasmiths.wordpress.com/category/business/gtd/

‘ Note      -   I moved all the main subrotuines of EzGTD to seperate users and
‘               class modules to ease future improvements and debugging. The
‘               calling format, taking the first statement as example is to run
‘               the EzGTD_Startup subrotuine in a user module named Startup

‘——————————————————————————-
   
    ‘The on button for my EzGTD routines
   
    Call Startup.EzGTD_Startup
       
End Sub

 

User Module Named GTDTasks

 

Option Explicit
Public g_blnNextContextTask As Boolean                  ‘A flag to simulate NextTask

Public Sub OpenNextContextTask(ByVal objTask As Outlook.TaskItem)

    ‘In outlook explorer, even if you group and sort, within the same categorization, the items
    ‘are still arranged with the taskitem.ToDoTaskOrdinal. The ToDoTaskOrdinal is sorted with
    ‘the decending sorting irregardless of other sorting settings, for example due date, status etc
   

    Dim colTaskItems As Outlook.Items
    Dim colRestrictItems As Outlook.Items
    Dim strFilter As String
   
    strFilter = "[ToDoTaskOrdinal] < ‘" & Format(objTask.TodoTaskOrdinal, "dd/MM/yyyy hh:mm AMPM") & _
                "’ AND NOT([Subject] = " & Support.AddApostrophe(objTask.subject) & ")"
 
    Set colTaskItems = g_objMainStore.GetDefaultFolder(olFolderTasks).Items
   
    Set colRestrictItems = colTaskItems.Restrict(strFilter)
    Call colRestrictItems.Sort("[ToDoTaskOrdinal]", True)
   
    ‘Last thing is to find those that have the same category
    Dim arry_Categories() As String
   
    arry_Categories = Split(objTask.categories, ",")
   
    ‘Find the taskitems that have the same FIRST category
   
    Const ProTag_Category As String = "urn:schemas-microsoft-com:office:office#Keywords"
   
    Dim strCategory As String
    strCategory = Trim(arry_Categories(0))

    Dim strCategoryFilter As String
    strCategoryFilter = "@SQL=" & AddQuotes(ProTag_Category) & " = ‘" & strCategory & "’"

    If colRestrictItems.Count > 1 Then
   
        Dim objNewTask As Outlook.TaskItem

        Set objNewTask = colRestrictItems.Find(strCategoryFilter)
       
        ‘If something is found, display it
        If Not objNewTask Is Nothing Then
       
            Call objNewTask.GetInspector.Activate
           
        End If
       
    End If
   
    ‘Clean up
    Set objNewTask = Nothing
    Set colRestrictItems = Nothing
    Set colTaskItems = Nothing
     
End Sub

 

User Module Named Inspectors

 

Option Explicit

Private g_Inspectors As New InspectorsEvents

‘To declare inspector object wiht even handling, the outlook object module
‘refuse to allow declaration using arrays, so I have to bypass it using this
‘manner of and declare each one seperately. Then use a function to track which
‘one is available when the previous inspector closed. The max can be easily
‘increase by copy and paste the handling codes

Private Const max_eInspector As Integer = 5
Private g_Inspector0 As New InspectorEvents
Private g_Inspector1 As New InspectorEvents
Private g_Inspector2 As New InspectorEvents
Private g_Inspector3 As New InspectorEvents
Private g_Inspector4 As New InspectorEvents

‘This is the last eInspector that falls back to the default Outlook
‘ implementation of new inspector with event handling if the user open too many
‘ inspectors in excess of the the max above

Private g_Inspector As New InspectorEvents

‘Array to track eInspectors allocations in a round robin manner
Private arr_eInspector(max_eInspector) As String

         
‘——————————————————————————-

‘ Name      -   Inspectors
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Create and handling events of inspectors and inspector objects
‘           -   to implement new NextContext featuers for taskitems

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   The items to handle events for

‘ Return    -   None

‘ Reference -   Inspectors
http://msdn.microsoft.com/en-us/library/ff870887.aspx

‘ Note      -   Default event handlers have severe limitations. Overcame by
‘           -   artificial handling in User module Inspectors.

‘——————————————————————————-

Public Sub Start_Inspectors_EventHandlers(strDummy As String)
   
    Call g_Inspectors.Init_eInspectors_EventHandlers
   
End Sub

Public Sub Create_eInspector(ByVal objInspector As Outlook.Inspector)

    ‘I want to handle only Taskitem, as I want to have more capabilities
   
    Select Case objInspector.CurrentItem.Class
   
   
    Case olTask
   
        Dim intCount As Integer
       
        intCount = Find_eInspectorSlot("")
       
        Select Case intCount
       
            ‘ If correct empty slot, create each item, then register the
            ‘ eInspector to that slot. The slot will be emptied by the
            ‘ eInspector_close routine for maintenance
           
            Case 0
                Call g_Inspector0.Init_eInspector_EventHandlers(objInspector)

            Case 1
                Call g_Inspector1.Init_eInspector_EventHandlers(objInspector)

            Case 2
                Call g_Inspector2.Init_eInspector_EventHandlers(objInspector)

            Case 3
                Call g_Inspector3.Init_eInspector_EventHandlers(objInspector)

            Case 4
                Call g_Inspector4.Init_eInspector_EventHandlers(objInspector)

            Case Else
                ‘This is the exception case
                Call g_Inspector.Init_eInspector_EventHandlers(objInspector)
        End Select
       
        If intCount < max_eInspector Then
       
            arr_eInspector(intCount) = objInspector.CurrentItem.EntryID
           
        End If
           
       
    End Select
   
End Sub

Public Sub Close_eInspector(ByVal objInspector As Outlook.Inspector)

    ‘Mark the eInspector slot as empty if the outlook item EntryID in inspector being closed
    ‘Matches any of the eInspector registered for Events Handling
   
    Dim intCount As Integer
   
    intCount = Find_eInspectorSlot(objInspector.CurrentItem.EntryID)
   
   
    If intCount < max_eInspector Then
       
        ‘MsgBox "eInspector Number – " & intCount & " item" & objInspector.Caption & " is closing"
        arr_eInspector(intCount) = ""
       
        ‘If the user wanted to show the next task with the same context, open the inspector

        If g_blnNextContextTask = True Then Call GTDTasks.OpenNextContextTask(objInspector.CurrentItem)
       
    End If
               
End Sub

Private Function Find_eInspectorSlot(strCompare As String) As Integer

 
    Dim intCount As Integer
   
    For intCount = 0 To UBound(arr_eInspector)
   
        ‘If it is an empty string, it is available
        If arr_eInspector(intCount) = strCompare Then
       
            Find_eInspectorSlot = intCount
           
            Exit Function
           
        End If
       
    Next
   
    ‘Assume non found, so return a exception integer count
   
    ‘Find_eInspectorSlot = max_eInspector + 1
    Find_eInspectorSlot = UBound(arr_eInspector) + 1
   

End Function

 

 

User Module Named Startup

 

Option Explicit

‘——————————————————————————-
‘ g_strDummy – Hide sub/function from Macros menu when user press Alt-F8
‘ g_strMainStore – The default store object
‘——————————————————————————-

Public g_objApp               As Outlook.Application
Public g_objNS                As Outlook.NameSpace
Public g_objAESelection       As Outlook.Selection
Public g_objMainStore         As Outlook.Store
Public g_objGmailStore        As Outlook.Store
Public g_strDummy             As String

‘——————————————————————————-
‘ Name      -   EzGTD_Startup
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   –

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   None

‘ Return    -   None

‘ Reference -   See
https://ideasmiths.wordpress.com/category/business/gtd/

‘ Note      –
‘——————————————————————————-

Public Function EzGTD_Startup()

‘Setup standard outlook objects that is repeatively used in all other modules

    Set g_objApp = Outlook.Application
    Set g_objNS = g_objApp.GetNamespace("MAPI")
    Set g_objAESelection = g_objApp.ActiveExplorer.Selection
    Set g_objMainStore = g_objNS.GetDefaultFolder(olFolderInbox).Store
    Set g_objGmailStore = Support.GetGmailStore(g_strDummy)

   
‘Start event handling for inspectors and inspector for GTD taskitems features
   
    Call Inspectors.Start_Inspectors_EventHandlers(g_strDummy)

End Function

 

User Module Named Support

 

Option Explicit

‘*******************************************************************************************************************
‘   Name            -       Various subroutine and Function as named
‘   Created by      -       Ryan Lim ideasmiths@gmail.com

‘   Purpose         -       Some useful procedures, see comment of each to see its purpose

‘   Change Log      –
‘                   -       1.0 Dated 12 May 2011

‘   Arguments       -       Various as needed

‘   Return          -       None


‘   Outlook Version -       From Outlook 2010
‘********************************************************************************************************************

Public Sub OpenContactitem()

    ‘Routine to try to find a contact from the selection that a user made
   
    Dim strSelection    As String
    Dim objSel          As Word.Selection
    Dim objDoc          As Word.Document

    Set objDoc = g_objApp.ActiveInspector.WordEditor
    Set objSel = objDoc.Windows(1).Selection
   
    strSelection = Trim(objSel.text)
   
    If InStr(1, strSelection, "’") > 0 Then
        strSelection = Left(strSelection, InStr(1, strSelection, "’") – 1)
    End If
   
    Dim objFolder As Outlook.Folder
    Dim objContactsItem As Outlook.Items
   
    Set objFolder = g_objNS.GetDefaultFolder(olFolderContacts)
    Set objContactsItem = objFolder.Items.Restrict("[File As] = " & AddApostrophe(strSelection))

    If objContactsItem.Count > 0 Then

            Dim objContact As Outlook.ContactItem
            Set objContact = objContactsItem.GetFirst
            objContact.GetInspector.Activate
    End If

End Sub

Public Sub NextContextTask()

    ‘Use as a macro to enable a switch so that if an eInspector closes, the next task
    ‘with the same context will be shown
   
    If g_blnNextContextTask = True Then
   
        g_blnNextContextTask = False

    Else
        g_blnNextContextTask = True
           
    End If
   
End Sub

Public Function AddQuotes(ByVal strString As String) As String

    AddQuotes = Chr(34) & strString & Chr(34)
   
End Function

Public Function AddApostrophe(ByVal strString As String) As String

    AddApostrophe = Chr(39) & strString & Chr(39)
   
End Function

Public Function EscapeString(ByVal strString As String) As String

    ‘This function is needed for DASL string submitted for search or filter, if it contains
    ‘Single quote, it will be return with escaped character

        Dim SingleQuote As String
        SingleQuote = Chr(39)
   
    ‘Create an array to store all the substrings
        Dim arrSingleQuote() As String

    ‘Break into parts those delimited with singleQuote
        arrSingleQuote = Split(strString, SingleQuote)

    ‘Join all parts of the string back with the escape
   
        EscapeString = Join(arrSingleQuote, "”")
   
End Function

Public Function SelectCategories(strDummy As String) As String

‘Creates a dummy journal item to access ShowCategoriesDialog
‘After user select the categories, return user selected categories to user

    Dim objJournalItem As Outlook.JournalItem
   
    Set objJournalItem = Application.CreateItem(olJournalItem)
    objJournalItem.ShowCategoriesDialog
   
    SelectCategories = objJournalItem.categories
   
    ‘Clean up
    Set objJournalItem = Nothing
   
End Function

Sub OpenContactLinks()

‘From an open contactitem, this macro will open all the contactitems in the links colection

Dim objItem As Object
Dim objLink As Outlook.Link

    On Error GoTo ContactNotFound
           
    Set objItem = g_objApp.ActiveInspector.CurrentItem
   
    If Not objItem.Links.Count = 0 Then
   
        For Each objLink In objItem.Links
   
            ‘As on 12 May 2010, the Microsoft documented link object points to a contactitem
           
            objLink.item.GetInspector.Activate

        Next

    End If
   
‘Clean Up

Set objItem = Nothing
Set objLink = Nothing

    Exit Sub
   
ContactNotFound:

    MsgBox "Contact " & objLink.Name & " is not found" & "Do you want Outlook to do a seach?"

End Sub

Public Function GetGmailStore(strDummy As String) As Outlook.Store

‘——————————————————————————-
‘ Find the name of the Gmail or IMAP store in this outlook session, I named mine
‘ as "Gmail", other people may use other names
‘ See Reference
http://msdn.microsoft.com/en-us/library/ff867485.aspx

‘ This function will return an empty string if there is no IMAP account in this
‘ outlook profile
‘——————————————————————————-
   
‘Start with an empty string so function returns it if no Imap account found
   
    Set GetGmailStore = Nothing
   
    On Error GoTo ErrorGenie

        Dim objAccount As Outlook.Account
       
        For Each objAccount In g_objNS.Accounts
       
            If objAccount.AccountType = olImap Then
   
                Set GetGmailStore = objAccount.DeliveryStore
               
                Exit For
               
            End If
           
        Next
       
        ‘Clean up
       
        Set objAccount = Nothing
   
    Exit Function
   
ErrorGenie:
   
    MsgBox "I suck at Programming…GetGmailstore"
   
End Function

 

Class Module Named InspectorEvents

 

Option Explicit

Private WithEvents eInspector As Outlook.Inspector

‘——————————————————————————-

‘ Name      -   eInspector
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Event Handlers for Inspectors Object

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   The items to handle events for

‘ Return    -   None

‘ Reference -   Inspectors
http://msdn.microsoft.com/en-us/library/ff870883.aspx

‘ Note      -   Default event handlers have severe limitations. Overcame by
‘           -   artificial handling in User module Inspectors.

‘——————————————————————————-

Public Sub Init_eInspector_EventHandlers(ByVal objInspector As Outlook.Inspector)
  
    Set eInspector = objInspector
 
End Sub
   

Private Sub eInspector_Close()

    ‘In my implimentation, there can be many einspector objects, each with events
    ‘handling capabilites unlike the limited Outlook Object implementation which
    ‘can only have 1 inspector object with events handling capabilities. The sub
    ‘in the User Module Inspectors will handle the proper closing of the
    ‘einspectors arrays, marking the slot as empty and releasing it for reuse
   
    Call Inspectors.Close_eInspector(eInspector)

End Sub

   

Private Sub Class_Terminate()

    ‘Clean up
   
    Set eInspector = Nothing
   
End Sub

Class Module Named InspectorsEvents

Option Explicit

Private WithEvents eInspectors As Outlook.Inspectors

‘——————————————————————————-

‘ Name      -   eInspectors
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Event Handlers for Inspectors Object

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   The items to handle events for

‘ Return    -   None

‘ Reference -   Inspectors
http://msdn.microsoft.com/en-us/library/ff870887.aspx

‘ Note      -   Default event handlers have severe limitations. Overcame by
‘           -   artificial handling in User module Inspectors.

‘——————————————————————————-

Public Sub Init_eInspectors_EventHandlers()

    On Error GoTo ErrorGenie
       
        Set eInspectors = g_objApp.Inspectors

    Exit Sub
       
ErrorGenie:
       
    MsgBox "I suck at programming, error at Init_eInspectors_EventHandlers"
          
End Sub

Private Sub eInspectors_NewInspector(ByVal objInspector As Inspector)

‘The creation of inspectors with event handlers are in routines in the
‘User module named Inspectors.
   
    Call Inspectors.Create_eInspector(objInspector)
   
End Sub

Private Sub Class_Terminate()
   
    ‘Clean up
   
    Set eInspectors = Nothing
   
End Sub

Source code for Matching Gmail read and unread status in folders


 

The purpose of these VBA codes is explained in this post

1

Important

There are 5 modules you need to import into your VBA editor. Guide to installation and notes on my programming

Info for programmers

Basically I set up event handlers for items object. Each items object monitor a Gmail IMAP subscribed folders for changes. If there was an addition, it checks if that folder is the trash, if yes, it marked the email as unread.

If there was an itemchange event, it check if it was an email, then search the other folders for emails with the same subject and SendOn time (it’s crude, but it will work most of the time). You can’t use EntryID as each ‘same’ email has different EntryID in outlook implementation of IMAP. When it found the emails, it match the read/unread status of each email with the source email (ie the one that had change)

You can combine all the routines into thisoutlooksession. But my codes for EZGTD has went too broad and I had to break up into many modules to simplify my future improvements and debugging. The codes are shown here as a historical example for other programmers who need to explore Gmail IMAP. I haven’t seen anyone did this during my Google search B-)

 

Download

The source codes can be downloaded at my Public Skydrive folder. You can view the codes below, note if you copy and paste from this blog post, be aware some browsers will change the singlequote ‘ and doublequotes “” to something else and VBA editor will show as error. Just change them back after you copied

 

ThisoutlookSession

Option Explicit

Private Sub Application_Startup()

‘——————————————————————————-

‘ Name      -   Application_Startup
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Start my EZGTD program when Outlook launch

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   None

‘ Return    -   None

‘ Reference -   See
https://ideasmiths.wordpress.com/category/business/gtd/

‘ Note      -   I moved all the main subrotuines of EzGTD to seperate users and
‘               class modules to ease future improvements and debugging. The
‘               calling format, taking the first statement as example is to run
‘               the EzGTD_Startup subrotuine in a user module named Startup

‘——————————————————————————-
   
    ‘The on button for my EzGTD routines
   
    Call Startup.EzGTD_Startup
       
End Sub

‘——————————————————————————-
‘ These two event handlers are the only ones I cannot moved to other class
‘ modules as they are at the Application object level and thisoutlooksession is
‘ a class module by itself. These set a flag as true when the AdvancedSearch
‘ method is completed for gmail tagged searches

‘ Other class modules are object level events handlers that call subroutines
‘ or functions in user modules with similar name. For example, the event
‘ handlers in the class modules InspectorsEvents will call the sub/functions
‘ in a user module named Inspectors.
‘——————————————————————————-

Private Sub Application_AdvancedSearchComplete(ByVal SearchObject As Search)

‘Mark the search flag as complete if AdvancedSearch completes it’s gmail search
   
    If SearchObject.Tag = "Gmail" Then

        g_blnAdvancedSearch_Gmail_Complete = True
       
    End If
   
End Sub

Private Sub Application_AdvancedSearchStopped(ByVal SearchObject As Search)

    If SearchObject.Tag = "Gmail" Then
   
        MsgBox "Search Stopped"
       
    End If
   
End Sub

User Module named Gmail

Option Explicit

‘——————————————————————————-
‘ These declare new objects that have event handling capabilities and is used
‘ to monitor various Gmail folders for item changes. These

‘ g_blnAdvancedSearch_Gmail_Complete
‘   – Use to inform concern subroutines that the AdvancedSearch has completed

‘——————————————————————————-

Public g_blnAdvancedSearch_Gmail_Complete       As Boolean

‘If you have more than 5 Gmail subscribed folders….add more variable declaration
Private g_GmailFolder1                          As New ItemsEvents
Private g_GmailFolder2                          As New ItemsEvents
Private g_GmailFolder3                          As New ItemsEvents
Private g_GmailFolder4                          As New ItemsEvents
Private g_GmailFolder5                          As New ItemsEvents

‘This is the Microsoft Schemas for Imap marked for deletion MAPI property
‘Const PropName As String = "
http://schemas.microsoft.com/mapi/id/{00062008-0000-0000-C000-000000000046}/85700003"

‘——————————————————————————-
‘ Name      -   Gmail
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Synchronise same email in different Gmail Folders when marked
‘           -   unread/read. This is a typical problem with Gmail IMAP
‘           -   implementation in Outlook.

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   None

‘ Return    -   None

‘ Reference -   See
https://ideasmiths.wordpress.com/category/business/gtd/

‘ Note      –
‘——————————————————————————-

Public Sub Monitor_ItemsInGmailFolders(strDummy As String)

‘Some of the Gmail folders may not be subscribed, so if error go to the next line
   
    On Error GoTo ErrorGenie

    If Not g_objGmailStore Is Nothing Then
   
        Dim intCount As Integer
        Dim objFolders As Outlook.Folders
       
        Set objFolders = g_objGmailStore.GetRootFolder.Folders

        intCount = 0

        ‘Assign an items object to each Gmail Subscribed Folder. As we don’t
        ‘know what names these folders have, have to do it the brute force way

        If intCount < objFolders.Count Then
       
            Call g_GmailFolder1.Start_eItems_EventHandlers _
             (objFolders.item(1).Items)
             intCount = intCount + 1
            
        End If

        If intCount < objFolders.Count Then
       
            Call g_GmailFolder2.Start_eItems_EventHandlers _
             (objFolders.item(2).Items)
             intCount = intCount + 1

        End If
       
        If intCount < objFolders.Count Then
       
            Call g_GmailFolder3.Start_eItems_EventHandlers _
             (objFolders.item(3).Items)
             intCount = intCount + 1

        End If
       
        If intCount < objFolders.Count Then
       
            Call g_GmailFolder4.Start_eItems_EventHandlers _
             (objFolders.item(4).Items)
             intCount = intCount + 1

        End If
       
        If intCount < objFolders.Count Then
       
            Call g_GmailFolder5.Start_eItems_EventHandlers _
             (objFolders.item(5).Items)
             intCount = intCount + 1

        End If
       
    Else
   
        MsgBox "There is no Gmail or other IMAP Accounts"
       
    End If
   
    ‘Clean up
   
    Set objFolders = Nothing
    Exit Sub
   
ErrorGenie:
   
    MsgBox "I suck at Programming – Monitor_ItemsInGmaiLFolders"

End Sub

Public Sub MatchItemUnread(ByVal objItem As Object)
   
‘——————————————————————————-
‘ Find ALL subscribed Gmail Folders for any items that have the same subject
‘ and SendOn Dates as objItem, then mark the results with the same unread
‘ status of the calling email
‘——————————————————————————-

‘This is unfortunate, I cannot solve Outlook IMAP Synchronisation and deletion
   
    On Error Resume Next

    Dim objResults As Outlook.Results
    Dim objResult As Object
   
‘Find any outlook items that have the same subject as the source
   
    Set objResults = AdvanceSearch_AllGmailFolders(objItem).Results

    If Not objResults Is Nothing Then
           

‘Any of the results have the same submited date/time with source email
           
        For Each objResult In objResults
   
                If objResult.SentOn = objItem.SentOn Then
          
‘Only change the unread status of the results if different with the source
‘because the itemchange event could have been caused by some other properties
‘changes such as delete
                   
                    If Not objResult.UnRead = objItem.UnRead Then
                   
                        objResult.UnRead = objItem.UnRead
                       
                    End If
               
                End If
                   
        Next
       
    End If
        
   
    ‘Clean up
   
    Set objItem = Nothing
    Set objResult = Nothing
    Set objResults = Nothing
   
End Sub

Private Function AdvanceSearch_AllGmailFolders(ByVal objItem As Object) As Outlook.Search

‘Use subject to search in Gmail folders to try to identify them as the same email,
‘although they could exist in multiple folders, like inbox, sent email and All mail
‘this is an unfortuate implementation of IMAP in outlook 2010
   
    Const ProTag_Subject As String = "
http://schemas.microsoft.com/mapi/proptag/0x0037001F"
   
    Dim strDASLsubject As String
    Dim strSubject As String

‘Escape the single,double and character in the string
    strSubject = Support.EscapeString(objItem.subject)

‘Format the ProTag for search subject into DASL format needed by AdvancedSearch
    strDASLsubject = "(" & Support.AddQuotes(ProTag_Subject) & " = " & _
                           Support.AddApostrophe(strSubject) & ")"
   
‘Set to search from the Gmail root folder and all subfolders such as ALL Mail, sent etc
    Dim objSearch As Search
    Dim strScope As String
   
    strScope = "’" & g_objGmailStore.GetRootFolder.FolderPath & "’"
   
    g_blnAdvancedSearch_Gmail_Complete = False

    Set objSearch = Application.AdvancedSearch _
        (Scope:=strScope, Filter:=strDASLsubject, SearchSubFolders:=True, Tag:="Gmail")

‘Test if the Advanced Serach has been completed, if not pass CPU time back to system
    
    While g_blnAdvancedSearch_Gmail_Complete <> True
   
        DoEvents
       
    Wend
   
‘Return the results
    Set AdvanceSearch_AllGmailFolders = objSearch
   
‘Clean up

    Set objSearch = Nothing
   
End Function

 

User Module named Startup

 

Option Explicit

‘——————————————————————————-
‘ g_strDummy – Hide sub/function from Macros menu when user press Alt-F8
‘ g_strMainStore – The default store object
‘——————————————————————————-

Public g_objApp               As Outlook.Application
Public g_objNS                As Outlook.NameSpace
Public g_objAESelection       As Outlook.Selection
Public g_objMainStore         As Outlook.Store
Public g_objGmailStore        As Outlook.Store
Public g_strDummy             As String

‘——————————————————————————-
‘ Name      -   EzGTD_Startup
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   –

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   None

‘ Return    -   None

‘ Reference -   See
https://ideasmiths.wordpress.com/category/business/gtd/

‘ Note      –
‘——————————————————————————-

Public Function EzGTD_Startup()

‘Setup standard outlook objects that is repeatively used in all other modules

    Set g_objApp = Outlook.Application
    Set g_objNS = g_objApp.GetNamespace("MAPI")
    Set g_objAESelection = g_objApp.ActiveExplorer.Selection
    Set g_objMainStore = g_objNS.GetDefaultFolder(olFolderInbox).Store
    Set g_objGmailStore = Support.GetGmailStore(g_strDummy)

‘Start EzGTD features for Gmail IMAP based emails

    Call Gmail.Monitor_ItemsInGmailFolders(g_strDummy)

End Function

 

User Module Named Support

Option Explicit

‘*******************************************************************************************************************
‘   Name            -       Various subroutine and Function as named
‘   Created by      -       Ryan Lim ideasmiths@gmail.com

‘   Purpose         -       Some useful procedures, see comment of each to see its purpose

‘   Change Log      –
‘                   -       1.0 Dated 12 May 2011

‘   Arguments       -       Various as needed

‘   Return          -       None


‘   Outlook Version -       From Outlook 2010
‘********************************************************************************************************************

Public Sub OpenContactitem()

    ‘Routine to try to find a contact from the selection that a user made
   
    Dim strSelection    As String
    Dim objSel          As Word.Selection
    Dim objDoc          As Word.Document

    Set objDoc = g_objApp.ActiveInspector.WordEditor
    Set objSel = objDoc.Windows(1).Selection
   
    strSelection = Trim(objSel.text)
   
    If InStr(1, strSelection, "’") > 0 Then
        strSelection = Left(strSelection, InStr(1, strSelection, "’") – 1)
    End If
   
    Dim objFolder As Outlook.Folder
    Dim objContactsItem As Outlook.Items
   
    Set objFolder = g_objNS.GetDefaultFolder(olFolderContacts)
    Set objContactsItem = objFolder.Items.Restrict("[File As] = " & AddApostrophe(strSelection))

    If objContactsItem.Count > 0 Then

            Dim objContact As Outlook.ContactItem
            Set objContact = objContactsItem.GetFirst
            objContact.GetInspector.Activate
    End If

End Sub

Public Function AddQuotes(ByVal strString As String) As String

    AddQuotes = Chr(34) & strString & Chr(34)
   
End Function

Public Function AddApostrophe(ByVal strString As String) As String

    AddApostrophe = Chr(39) & strString & Chr(39)
   
End Function

Public Function EscapeString(ByVal strString As String) As String

    ‘This function is needed for DASL string submitted for search or filter, if it contains
    ‘Single quote, it will be return with escaped character

        Dim SingleQuote As String
        SingleQuote = Chr(39)
   
    ‘Create an array to store all the substrings
        Dim arrSingleQuote() As String

    ‘Break into parts those delimited with singleQuote
        arrSingleQuote = Split(strString, SingleQuote)

    ‘Join all parts of the string back with the escape
   
        EscapeString = Join(arrSingleQuote, "”")
   
End Function

Public Function SelectCategories(strDummy As String) As String

‘Creates a dummy journal item to access ShowCategoriesDialog
‘After user select the categories, return user selected categories to user

    Dim objJournalItem As Outlook.JournalItem
   
    Set objJournalItem = Application.CreateItem(olJournalItem)
    objJournalItem.ShowCategoriesDialog
   
    SelectCategories = objJournalItem.categories
   
    ‘Clean up
    Set objJournalItem = Nothing
   
End Function

Sub OpenContactLinks()

‘From an open contactitem, this macro will open all the contactitems in the links colection

Dim objItem As Object
Dim objLink As Outlook.Link

    On Error GoTo ContactNotFound
           
    Set objItem = g_objApp.ActiveInspector.CurrentItem
   
    If Not objItem.Links.Count = 0 Then
   
        For Each objLink In objItem.Links
   
            ‘As on 12 May 2010, the Microsoft documented link object points to a contactitem
           
            objLink.item.GetInspector.Activate

        Next

    End If
   
‘Clean Up

Set objItem = Nothing
Set objLink = Nothing

    Exit Sub
   
ContactNotFound:

    MsgBox "Contact " & objLink.Name & " is not found" & "Do you want Outlook to do a seach?"

End Sub

Public Function GetGmailStore(strDummy As String) As Outlook.Store

‘——————————————————————————-
‘ Find the name of the Gmail or IMAP store in this outlook session, I named mine
‘ as "Gmail", other people may use other names
‘ See Reference
http://msdn.microsoft.com/en-us/library/ff867485.aspx

‘ This function will return an empty string if there is no IMAP account in this
‘ outlook profile
‘——————————————————————————-
   
‘Start with an empty string so function returns it if no Imap account found
   
    Set GetGmailStore = Nothing
   
    On Error GoTo ErrorGenie

        Dim objAccount As Outlook.Account
       
        For Each objAccount In g_objNS.Accounts
       
            If objAccount.AccountType = olImap Then
   
                Set GetGmailStore = objAccount.DeliveryStore
               
                Exit For
               
            End If
           
        Next
       
        ‘Clean up
       
        Set objAccount = Nothing
   
    Exit Function
   
ErrorGenie:
   
    MsgBox "I suck at Programming…GetGmailstore"
   
End Function

 

Class Module named ItemsEvents

Option Explicit

Private WithEvents eItems As Outlook.Items

‘——————————————————————————-

‘ Name      -   Start_eItems_EventHandlers
‘ Created   -   Ryan Lim ideasmiths@gmail.com

‘ Purpose   -   Event Handlers for outlook items object
‘           -   Use to enhance IMAP implementation in Outlook, the default is
‘           -   each email exist with different EntryID if they are labelled in
‘           -   the gmail, for example one email in inbox also exist in All Mail
‘           -   so when this is read, it will show unread in the inbox but still
‘           -   show up as unread in the All Mail folder.

‘           -   The itemchange event handler will match and mark with same status
‘           -   The add event handler will mark emails moved to trash as unread

‘ Version   -   1.0 dated 15 May 2011 First version

‘ Arguments -   The items to handle events for

‘ Return    -   None

‘ Reference -   Items
http://msdn.microsoft.com/en-us/library/ff870897.aspx

‘ Note      -   None

‘——————————————————————————-

Public Sub Start_eItems_EventHandlers(ByVal objItems As Outlook.Items)

    Set eItems = objItems
       
End Sub

Private Sub eItems_ItemChange(ByVal objItem As Object)

    Call Gmail.MatchItemUnread(objItem)

End Sub

Private Sub eItems_ItemAdd(ByVal objItem As Object)

‘——————————————————————————-
‘ This event handler will mark the Gmail Trash email that was just added as read
‘ In the future need to check if the original item was unread or not. As on 15
‘ May 2011 it is difficult as Outlook Imap Synchronisation and implementation
‘ does not fire the events with predictability.

‘ Important, in my Gmail, the folder "Trash" holds the deleted emails, change it
‘ to your settings as yours may have different name
‘——————————————————————————-
           
    If objItem.Parent = g_objGmailStore.GetDefaultFolder(olFolderDeletedItems) Then
    ‘GetFolder(g_strGmailStore, "Trash") Then
               
        objItem.UnRead = False
        objItem.Save
                   
    End If
           
        ‘Clean up
           
    Set objItem = Nothing

End Sub

Private Sub Class_Terminate()

    ‘Clean up
   
    Set eItems = Nothing
   
End Sub

Solution–Matching the read and unread status of emails in different Gmail IMAP folders


 

The macros and installation guides are stored in this blog post

 

Background

The implementation of IMAP in Outlook 2010 means that a few folders are created and each folder store an email that correspond to it’s original in Gmail. Unfortunately, in Gmail, most emails are ‘duplicated’. For example, when an email comes in, it will be stored in the “inbox”, and also the “All Mail” and perhaps the “Important mail”. If you have a filter setup in Gmail, this email could also show up under one or more label.

On Outlook 2010 side, the problem occurs this ONE email will show up as different emails in the folders “inbox”,"All mail” etc. It may looks the same, but Outlook Programmers who check the EntryID property will soon find out that each have a different ID, even though everything else like subject, sender/recipent are the same!

So if you read an email in the Inbox and it shows as read, you may be surprise that the same one still shows as unread in the All Mail! If you read it, then delete it, it will show up as unread in the Trash folder. Won’t you go crazy trying to figure out which email has already been read?

1

Solution

One solution was to reduce the number of subscribed folders to the minimum, but it is still irritating. Well, I came up with some VBA routine that runs in the background to match the read/unread status, trying to be as user friendly as possible. For example, if you go to the All mail and flag an email as unread, it will show as unread in the other Folders. A deleted mail will be unread when it enters the Trash Folder and so on.

Caveat

Because of the way Outlook  2010 implement IMAP and synchronisation, it was impossible for me to detect the ‘marked for deletion’ (the strikethrough you see on a deleted mail), so it will still stay in the inbox till you press F9 or synchronise the mail.

In some circumstances the routines will fail and you will see an error, press end and continue from there. This occurs when Outlook cannot complete synchronisation of the “All Mail” folder due to slow network or you had several large attachments. At the same time, the item in inbox was deleted and showed up in the Trash and it in return tries to change the status of the same email in the All Mail folder and crash. Blame Microsoft for this, I can’t  solve it (yet).

Have fun and please report any bugs/problems or improvement you would like to see.

Solved : Use outlook VBA to create a custom Gmail Send/Receive Group in Outlook 2010


 

By default, Outlook puts all the email account in the All Accounts Send/Receive Groups as shown. But sometimes I just want to check the Gmail inbox for some new emails.

The ONLY Send/Receive Groups you can add  with program as of now is the Application Folders Send/Receive Group.  However, note that it can only add in the folders you want to synchronise, the rest of the settings you have to manually change.

2

 

My example codes below will only activate the inbox of the Gmail for synchronisation. It will deselect the other subscribed folders such as “All Mails” and “Junk E-mail”. After checking the inbox for your purpose, you can turn on all the Gmail folders for synchronisation again by modifiying the codes below.

1

The codes are in 2 modules, one in the class module and the other a user module. These are for my needs.

 

These codes are in a Class Module named SyncObjectEvents

 

Option Explicit

Public WithEvents eSyncObject As Outlook.SyncObject

Public Sub Init_eSyncObject(ByVal strStore As String, ByVal strFolder As String)
   
    On Error GoTo ErrorGenie
   
    ‘Flag the folder in the store as enabled for synchronisation with the AppFolder
       
    Dim objFolder As Outlook.Folder
   
    For Each objFolder In Outlook.Application.Session.Stores.item(strStore).GetRootFolder.Folders
   
        If objFolder.Name = strFolder Then
            objFolder.InAppFolderSyncObject = True
        Else
            objFolder.InAppFolderSyncObject = False
        End If
    Next
   
    ‘Set the folder to be Synchronize using the SyncObject with Event Handling capabilities
    Set eSyncObject = Application.Session.SyncObjects.AppFolders

    Exit Sub
   
ErrorGenie:

    Const Message1 As String = "This event handler was trying to be created for SyncObject with the name -"
    Const Message2 As String = "Check your outlook Send/Receive Group to see if this Email Account Exist"
    Const Message3 As String = "If not, try All Account to see if it works"
   
    MsgBox Message1 & strStore & strFolder & vbLf & Message2 & vbLf & Message3

End Sub

 

These code are in a User Module that calls the class module

 

Option Explicit

Dim m_GmailSyncObject As New SyncObjectEvents 

Sub TestGmailInboxSync ()

Call m_GmailSyncObject.Init_eSyncObject("Gmail", "Inbox")
m_GmailSyncObject.eSyncObject.Start

End Sub

Information about my outlook codes and bug reporting


 

I did the programming and test on Outlook 2010. It may work unmodified on Outlook 2007 .

These will not work on Outlook 2000/2003 as some methods/properties are only available on 2007/2010 versions.

If you encounter any errors, please download faststone capture and take a screen shot of that error. Upload to imgur.com and post that image link in a comment at the blog post on that macro. I will try to kill the bug.

Running Solution Module in a class module called by Outlook or other VBA routines


 

This is a continuation of my trial of setting up a solution Module to run my EzGTD macros so that I can use Outlook 2010 as my GTD inbox

If thisoutlooksession looks crowded, you can move some of the codes into a class module. Then call the class module functions from thisoutlooksession_startup if you need it to automatically start with Outlook or from other VBA routines if you want to have on-demand functions.

In this example, i am going to put the routine to create a solution module that shows up in the navigation pane of outlook.

Put these codes into thisoutlooksession

 

Option Explicit

Dim m_SearchModule As New AddSolutionModule

Private Sub Application_Startup()

‘Create a Solution Module for EzGTD
   
    ‘The EzGTD Folder Name, you can change it
    Const strFolderName As String = "EzGTD"
 
    Call m_SearchModule.CreateSolutionModule(strFolderName)
   
End Sub

6

Put these code into a class module with name AddSolutionModule

Option Explicit

‘This routine would create a new folder EzGTD if it does not already exist
‘Then it would try to start the Solution Module so that it will show up in
‘The outlook Navigation Panel

‘Programmed by Ryan Lim ideasmiths@gmail.com
‘version 1.0 dated 3 may 2011

Public Sub CreateSolutionModule(ByVal strFolderName)
   
    Dim objFolder As Outlook.Folder
   
    ‘Try to find the folder needed by Solution Module
    Set objFolder = objSMFolder(strFolderName)
   
    ‘Turn on the Solution Module
    Dim objSolModule As SolutionsModule
   
    Set objSolModule = Application.ActiveExplorer.NavigationPane.Modules.GetNavigationModule(olModuleSolutions)
   
    With objSolModule
        .AddSolution objFolder, olShowInDefaultModules
        .Visible = True
    End With
   
    ‘Clean up
    Set objFolder = Nothing
    Set objSolModule = Nothing

End Sub

Private Function objSMFolder(ByVal strFolderName As String) As Outlook.Folder
   
    ‘Try to add a folder to the root folder, if it already exist an error will occur
   
    On Error GoTo ErrorGenie

        Set objSMFolder = Application.Session.GetDefaultFolder(olFolderInbox).Parent.Folders.Add(strFolderName)

    Exit Function

ErrorGenie:

    ‘The folder EzGTD may already have been created, in this case just select it
   
        Set objSMFolder = Application.Session.GetDefaultFolder(olFolderInbox).Parent.Folders.item(strFolderName)

End Function

 

Outlook 2010 GTD settings with Gmail IMAP


Follow the Gmail guide to setup the IMAP settings for outlook 2007 or 2010.

Below are some of my own GTD settings to make Outlook work well with Gmail. These ideas are from various googled postings and I assembled what makes sense to me here

IDEA 1 – Subscribing to the minimum gmail folders you need for GTD

Gmail Subscribed Folders

After you subscribed to the folders, you would want to change if only the message headers or the full message (message header + body + attachments) are downloaded each time you press the Send/Receive button.

This is because inside Gmail All Mail folder or sent folder, there might be thousands of emails with up to GB of attachments! If  you skip this step, the next time you press Send/Receive, prepare to wait a long…long long time before you regain control of Outlook.

Message Header

Message Header 2

It is okay to keep Gmail All mail in outlook, as long as you download only the message headers and not everything

Gmail All Mail Folder Size

IDEA 2 – Change the connection to the server to be off line.

This is important because of the nature of IMAP. When you do something to an email in outlook, for example deleting it, if the connection is online, it will communicate with the Gmail server and this may cause lag, especially if you do that to a few emails at the same time.

Going offline means you can do all the actions you want on those emails, and the next time you press the Send/Receive button, outlook would then communicate these all at once to the Gmail server. This makes Outlook slightly ‘faster’

Offline

IDEA 3 – Make Gmail folders more presentable in Outlook

Root Folder

IDEA 4 – Sent and Delete Emails settings

see the about Gmail guide above on how to get to the settings

Gmail IMAP settings

My preferably way to setup the delete email in Gmail is to move the email to the trash folder of Gmail, which will automatically empty it 30 days later or when I press Empty folder in outlook. This step also removes the email from the Gmail All mail folder which keeps every email

Trash

 

IDEA 5 – Adding extra folders to ‘categorise’ gmail mails.

Each ‘folder’ you add in outlook, it actually creates a corresponding label in gmail. For example, if you create a new folder named archive, a label named archive shows up in Gmail.

Don’t create too many folders, or even archive your emails to these created folders. Gmail itself stores all the mails in the All Mail folder (some say permanently). So practise the simplicity in GTD, use the minimum folders needed.

Archive Folder

 

IDEA 6 – Adding Rules to Gmail IMAP

By default, your Gmail IMAP has no categories, you can create a rule to add a category for each email that comes in. After that, when you view the email, you have that option available

 

By default, there is no notification when new emails come in to your Gmail inbox. You can add a rule to show an online notification or play a sound

Example of creating a Solution Module in Outlook 2010 using VBA


 

In outlook 2010, there is a new but hidden option in the Navigation Pane. The solution module can only be ‘activated’ programmatically by giving it a root folder. SM, just like the other modules such as mail or contact, provides a place to store folders and outlook items. However, SM can store different types of items such as contact/task/mails all under one roof.

There is not much information on SM using VBA, I have googled and saw only one example from Microsoft explaining how to do this in C, a language which I had forgotten many years ago. So I cooked up a quick VBA example to show others how this may works.

Am thinking of using the solution module as my GTD setup @someday. Program outlook to startup in the Solution Module and go from there.

Step 1

Figure 1 – Adding the Folder before running the macro AND adding the Solution Module to the navigation pane after running the macro

Step 2

Figure 2 – Running the macro

Step 3

Figure 3 – Clicking on the solution Module in Navigation Pane

The code starts here, insert a module in outlook VBA editor (ALT F11), copy and paste, then run

 

Option Explicit

Private Sub CreateSolutionModule()

    Dim objPane As NavigationPane
    Dim objSolModule As SolutionsModule
   
    Dim objFolder As Outlook.folder

Set objPane = Application.ActiveExplorer.NavigationPane

Set objSolModule = objPane.Modules.GetNavigationModule(olModuleSolutions)

‘Let the User pick a folder to put into Solution Module
Set objFolder = Application.Session.PickFolder

‘Turn on the Solution Module
objSolModule.AddSolution objFolder, olShowInDefaultModules
objSolModule.Visible = True

End Sub

You can run these codes in a class module so that thisoutlooksession won’t be so clutted, example here