Attribute VB_Name = "bofen32" ' *** BOFEN'S AOL 4.0 32-BIT MODULE (v1.0) *** ' bofen@bofen.com ' http://www.bofen.com ' This module is intended for 32-Bit VB with AOL 4.0. Many subs/functions were ' coded with CodeGenie! Download CodeGenie from www.bofen.com! There are ' explanations on what the sub/function does and an example on how to use it! ' Everything in this sub was coded 100% by me. I made this instead of making ' another ao-prog. I'm just getting very sick of the ao-prog scene and I'm sick of ' making my own interfaces, they take forever! All the progs are the same, there's ' never anything new. So hopefully with this module some of you can create some ' new features on your progs. ' Want to learn Visual Basic to the fullest extent? Then "Mastering Visual Basic 5" ' is the book for you! (there is also the same book for vb6 users) These two books ' and many more programming books can be purchased from www.bofen.com! ' "Mastering Visual Basic 5" is the book I learned from... So it's got to be good! ;p ' Anything you want to see in the next version? Lemme here your ideas... Option Explicit ' Declarations Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (destination As Any, source As Any, ByVal Length As Long) Public Declare Function EnableWindow Lib "user32" (ByVal hWnd As Long, ByVal fEnable As Long) As Long Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long Public Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long Public Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long Public Declare Function GetMenu Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function GetSubMenu Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long Public Declare Function GetMenuItemCount Lib "user32" (ByVal hMenu As Long) As Long Public Declare Function GetMenuItemID Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long Public Declare Function GetMenuString Lib "user32" Alias "GetMenuStringA" (ByVal hMenu As Long, ByVal wIDItem As Long, ByVal lpString As String, ByVal nMaxCount As Long, ByVal wFlag As Long) As Long Public Declare Function GetPrivateProfileString Lib "kernel32" Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long Public Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hWnd As Long) As Long Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long Public Declare Function IsWindowVisible Lib "user32" (ByVal hWnd As Long) As Long Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long Public Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long Public Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, ByVal lpBaseAddress As Long, ByVal lpBuffer As String, ByVal nSize As Long, ByRef lpNumberOfBytesWritten As Long) As Long Public Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long Public Declare Function SendMessageByNum& Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) Public Declare Function SendMessageByString Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As String) As Long Public Declare Function SendMessageLong& Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) Public Declare Function SetCursorPos Lib "user32" (ByVal X As Long, ByVal Y As Long) As Long Public Declare Function SetParent Lib "user32" (ByVal hWndChild As Long, ByVal hWndNewParent As Long) As Long Public Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal Y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long Public Declare Function ShowWindow Lib "user32" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long Public Declare Function WritePrivateProfileString Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpString As Any, ByVal lpFileName As String) As Long ' Constants Public Const BM_GETCHECK = &HF0 Public Const BM_SETCHECK = &HF1 Public Const CB_GETCOUNT = &H146 Public Const CB_GETCURSEL = &H147 Public Const CB_GETITEMDATA = &H150 Public Const CB_SETCURSEL = &H14E Public Const SWP_NOMOVE = &H2 Public Const SWP_NOSIZE = &H1 Public Const FLAGS = SWP_NOMOVE Or SWP_NOSIZE Public Const HWND_NOTOPMOST = -2 Public Const HWND_TOPMOST = -1 Public Const LB_GETCOUNT = &H18B Public Const LB_GETITEMDATA = &H199 Public Const LB_GETTEXT = &H189 Public Const LB_GETTEXTLEN = &H18A Public Const LB_SETCURSEL = &H186 Public Const PROCESS_READ = &H10 Public Const RIGHTS_REQUIRED = &HF0000 Public Const SW_HIDE = 0 Public Const SW_MAXIMIZE = 3 Public Const SW_MINIMIZE = 6 Public Const SW_NORMAL = 1 Public Const SW_SHOW = 5 Public Const VK_DOWN = &H28 Public Const VK_RETURN = &HD Public Const VK_RIGHT = &H27 Public Const VK_SPACE = &H20 Public Const WM_CHAR = &H102 Public Const WM_CLOSE = &H10 Public Const WM_COMMAND = &H111 Public Const WM_DESTROY = &H2 Public Const WM_GETTEXT = &HD Public Const WM_GETTEXTLENGTH = &HE Public Const WM_KEYDOWN = &H100 Public Const WM_KEYUP = &H101 Public Const WM_LBUTTONDBLCLK = &H203 Public Const WM_LBUTTONDOWN = &H201 Public Const WM_LBUTTONUP = &H202 Public Const WM_SETTEXT = &HC ' Types Public Type POINTAPI X As Long Y As Long End Type Public Sub AcceptAIMRequest() ' This sub will accept the AIM acceptance request. Here is an example: ' Call AcceptAIMRequest If FindAIMAcceptWnd() = 0& Then Exit Sub Call ClickIcon(FindWindowEx(FindAIMAcceptWnd(), 0&, "_AOL_Icon", vbNullString)) End Sub Public Sub ActivateAOL() ' This sub will bring the AOL window to the top and set focus on it. Here is an example: ' Call ActivateAOL Dim AOLFrame As Long, TextLen As Long, AOLFrameTxt As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) TextLen& = SendMessage(AOLFrame&, WM_GETTEXTLENGTH, 0&, 0&) AOLFrameTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLFrame&, WM_GETTEXT, TextLen& + 1&, AOLFrameTxt$) Call AppActivate(AOLFrameTxt$) End Sub Public Sub AddAsciiCharacters(Ctrl As Control) ' This sub will add all the ascii characters to a control. ' This example will add the characters to a listbox control named List1. ' Call AddAsciiCharacters(List1) Dim i As Long For i& = 33& To 255& Ctrl.AddItem Chr(i&) Next i& End Sub Public Sub AddBuddyToBuddyList(Buddies As String, GroupName As String) ' This sub will add a buddy or buddies to one of the user's buddy groups. ' This example will add "Screenname" to the buddy group named "My Buddies". ' Call AddBuddyToBuddyList("Screenname", "My Buddies") ' This example will add 3 buddies to the buddy group named "My Buddies". ' Buddies$ = "Screenname 1" & Chr(13) & Chr(10) & "Screenname 2" & Chr(13) & Chr(10) & "Screenname 3" ' Call AddBuddyToBuddyList(Buddies$, "My Buddies") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, UpdateMsg As Long Dim AOLIcon As Long, i As Long, BuddyLists As Long, BuddyListsVis As Long, Button As Long Dim hProcess As Long, Index As Long, Item As String, ItemData As Long, Dest As Long Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long, AOLEdit As Long Dim Screenname As String, AOLListbox As Long, AOLStatic As Long, UpdateMsgVis As Long On Error Resume Next AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) If FindEditBuddyWnd() = 0& Then AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLIcon& And AOLListbox& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& AOLListbox& = FindWindowEx(BuddyLists&, 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(AOLListbox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLListbox&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLListbox&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Left(Item$, InStr(Item$, vbNullChar) - 1&) If Trim(LCase(Mid(Item$, 1&, Len(GroupName$)))) = LCase(Trim(GroupName$)) Then Call SelectItemFromListbox(AOLListbox&, Index&): Exit For Skip: Next Index& Call CloseHandle(hProcess&) AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(BuddyLists&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindEditBuddyWnd() End If AOLEdit& = FindWindowEx(FindEditBuddyWnd(), 0&, "_AOL_Edit", vbNullString) AOLEdit& = FindWindowEx(FindEditBuddyWnd(), AOLEdit&, "_AOL_Edit", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) For i& = 1& To GetLineCount(Buddies$) Screenname$ = GetLineFromText(Buddies$, i&) If IsValidScreenname(Screenname$) Then Call SetText(AOLEdit&, Screenname$) Call SendMessageByNum(AOLEdit&, WM_CHAR, 13&, 0&) Call Pause(1.5) End If Next i& AOLIcon& = FindWindowEx(FindEditBuddyWnd(), 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(FindEditBuddyWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents UpdateMsg& = FindWindow("#32770", "America Online") UpdateMsgVis& = IsWindowVisible(UpdateMsg&) Call Pause(0.1) Loop Until UpdateMsgVis& = 1& Button& = FindWindowEx(UpdateMsg&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents UpdateMsg& = FindWindow("#32770", "America Online") Call Pause(0.1) Loop Until UpdateMsg& = 0& Do: DoEvents Call Pause(0.1) Loop Until FindEditBuddyWnd() = 0& BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call CloseWindow(BuddyLists&) End Sub Public Sub AddCombobox(hWnd As Long, Ctrl As Control, CheckForDupe As Boolean) ' This sub will add all of the items in an AOL combobox control to a control ' control of your choice. You can also have the sub avoid adding duplicates ' to your control by setting CheckForDupe to True. ' This example will add all of the items in AOLCombobox& into a listbox ' control named List1 and will check for duplicates. ' AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) ' Call AddCombobox(AOLCombobox&, List1, True) Dim hProcess As Long, Index As Long, Item As String Dim ItemData As Long, Dest As Long, i As Long Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next Call GetWindowThreadProcessId(hWnd&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(hWnd&, CB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(hWnd&, CB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) If CheckForDupe = True Then For i& = 0& To Ctrl.ListCount - 1& If LCase(Ctrl.List(i&)) = LCase(Item$) Then GoTo SkipMe Next i& Ctrl.AddItem Trim(Item$) Else Ctrl.AddItem Trim(Item$) End If SkipMe: Next Index& Call CloseHandle(hProcess&) End Sub Public Sub AddFlashMail(Ctrl As Control) ' This sub will add your flashmail list to a control of your choice. ' This example will add the user's flashmail list to a listbox control ' named List1. ' Call AddFlashMail(List1) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLTree As Long, TxtLength As Long, i As Long Dim AOLTreeTxt As String, MailSubject As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") If AOLChild& = 0& Then Exit Sub AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) For i& = 0& To GetListCount(AOLTree&) - 1& TxtLength& = SendMessage(AOLTree&, LB_GETTEXTLEN, i&, 0&) AOLTreeTxt$ = String(TxtLength& + 1&, 0&) Call SendMessageByString(AOLTree&, LB_GETTEXT, i&, AOLTreeTxt$) MailSubject$ = Mid(AOLTreeTxt$, InStr(AOLTreeTxt$, vbTab) + 1&, Len(AOLTreeTxt$)) Ctrl.AddItem Mid(MailSubject$, InStr(MailSubject$, vbTab) + 1&, Len(MailSubject$)) Next i& End Sub Public Sub AddListbox(hWnd As Long, Ctrl As Control, CheckForDupe As Boolean) ' This sub will add all of the items in an AOL listbox control to a control ' of your choice. You can also have the sub avoid adding duplicates ' to your control by setting CheckForDupe to True. ' This example will add all of the items in AOLListbox& into a listbox ' control named List1 and will check for duplicates. ' AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) ' Call AddListbox(AOLListbox&, List1, True) Dim hProcess As Long, Index As Long, Item As String Dim ItemData As Long, Dest As Long, i As Long Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next Call GetWindowThreadProcessId(hWnd&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(hWnd&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(hWnd&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Trim(Left(Item$, InStr(Item$, vbNullChar) - 1&)) If CheckForDupe = True Then For i& = 0& To Ctrl.ListCount - 1& If LCase(Ctrl.List(i&)) = LCase(Item$) Then GoTo Skip Next i& Ctrl.AddItem Item$ Else Ctrl.AddItem Item$ End If Skip: Next Index& Call CloseHandle(hProcess&) End Sub Public Sub AddLoginScreennames(TheControl As Control) ' This will add the screennames from AOL's sign on screen ' to a control of your choice. ' This example will add the login screennames to a listbox ' control named List1. ' Call AddLoginScreennames(List1) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim SignOn As Long, Goodbye As Long, AOLCombobox As Long Dim RoomList As Long, hProcess As Long, Index As Long Dim ItemData As Long, Dest As Long, i As Long, Screenname As String Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") If SignOn& Then AOLChild& = SignOn&: GoTo SkipIt If Goodbye& Then AOLChild& = Goodbye& SkipIt: If AOLChild& = 0& Then Exit Sub AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) Call GetWindowThreadProcessId(AOLCombobox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLCombobox&, CB_GETCOUNT, 0&, 0&) - 1& Screenname$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLCombobox&, CB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Screenname$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Screenname$, 4&) Dest& = Dest& + 6& Screenname$ = String(16&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Screenname$, 16&, lpNumberOfBytesWritten&) TheControl.AddItem Trim(Screenname$) Next Index& Call CloseHandle(hProcess&) End Sub Public Sub AddNewMail(Ctrl As Control) ' This sub will add your new mail list to a control of your choice. ' This example will add the user's new mail list to a listbox control ' named List1. ' Call AddNewMail(List1) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLTree As Long, TxtLength As Long, i As Long Dim AOLTabControl As Long, AOLTabPage As Long Dim AOLTreeTxt As String, MailSubject As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") If AOLChild& = 0& Then Exit Sub AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTree& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Tree", vbNullString) For i& = 0& To GetListCount(AOLTree&) - 1& TxtLength& = SendMessage(AOLTree&, LB_GETTEXTLEN, i&, 0&) AOLTreeTxt$ = String(TxtLength& + 1&, 0&) Call SendMessageByString(AOLTree&, LB_GETTEXT, i&, AOLTreeTxt$) MailSubject$ = Mid(AOLTreeTxt$, InStr(AOLTreeTxt$, vbTab) + 1&, Len(AOLTreeTxt$)) Ctrl.AddItem Mid(MailSubject$, InStr(MailSubject$, vbTab) + 1&, Len(MailSubject$)) Next i& End Sub Public Sub AddRoomList(TheControl As Control, AddUser As Boolean, CheckForDupe As Boolean) ' This sub will add all of the screennames in the chatroom to a control ' of your choice. You can have it skip the user's screenname and also ' check for duplicates. ' This example will add the the screennames to a listbox named List1 ' and will not add the user's screenname and will check for duplicates. ' Call AddRoomList(List1, False, True) Dim RoomList As Long, hProcess As Long, Index As Long Dim ItemData As Long, Dest As Long, i As Long, Screenname As String Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next If FindChatWnd() = 0& Then Exit Sub RoomList& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(RoomList&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(RoomList&, LB_GETCOUNT, 0&, 0&) - 1& Screenname$ = String(4&, vbNullChar) ItemData& = SendMessage(RoomList&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Screenname$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Screenname$, 4&) Dest& = Dest& + 6& Screenname$ = String(16&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Screenname$, 16&, lpNumberOfBytesWritten&) Screenname$ = Left(Screenname$, InStr(Screenname$, vbNullChar) - 1&) If Screenname$ = AOLScreenname() And AddUser = False Then GoTo Skip If CheckForDupe = True Then For i& = 0& To TheControl.ListCount - 1& If LCase(TheControl.List(i&)) = LCase(Screenname$) Then GoTo Skip Next i& TheControl.AddItem Screenname$ Else TheControl.AddItem Screenname$ End If Skip: Next Index& Call CloseHandle(hProcess&) End Sub Public Sub AddScreenFonts(Ctrl As Control) ' This sub will add all of the user's fonts into a control of your choice. ' This example will add all of the user's fonts to a listbox named List1. ' Call AddScreenFonts(List1) For i& = 0& To Screen.FontCount - 1& Ctrl.AddItem Screen.Fonts(i&) Next i& End Sub Public Sub AddToAddressBook(FirstName As String, LastName As String, EmailAddress As String, Notes As String) ' This sub will add a person to the user's AOL address book. Here's an example... ' Call AddToAddressBook("John", "Doe", "johndoe@hotmail.com", "The coolest guy in the world!") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim NewPersonWndVis As Long, AOLIcon As Long, NewPersonWnd As Long Dim AOLTabPage As Long, AOLEdit As Long, AOLTabControl As Long Call RunPopupMenu(3&, 6&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Address Book") AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLTree& And AOLIcon& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents NewPersonWnd& = FindWindowEx(MDIClient&, 0&, "AOL Child", "New Person") NewPersonWndVis& = IsWindowVisible(NewPersonWnd&) Call Pause(0.25) Loop Until NewPersonWndVis& = 1& AOLTabControl& = FindWindowEx(NewPersonWnd&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLEdit& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, FirstName$) AOLEdit& = FindWindowEx(AOLTabPage&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, LastName$) AOLEdit& = FindWindowEx(AOLTabPage&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, EmailAddress$) AOLEdit& = FindWindowEx(AOLTabPage&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Notes$) DoEvents AOLIcon& = FindWindowEx(NewPersonWnd&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents NewPersonWnd& = FindWindowEx(MDIClient&, 0&, "AOL Child", "New Person") Call Pause(0.1) Loop Until NewPersonWnd& = 0& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Address Book") Call CloseWindow(AOLChild&) End Sub Public Sub AddToFavoritePlaces(Place As String, Address As String) ' This sub will add Place$ to AOL's Favorite Places. Place is the name/description ' of the Address$. Address$ is the "URL" of the Place$. Here's an example: ' This example will add "bofen.com" to AOL's Favorite Places. ' Call AddToFavoritePlaces("bofen.com", "http://www.bofen.com") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim AOLIcon As Long, AddNew As Long, AddNewVis As Long, AOLEdit As Long Call RunPopupMenu(7&, 1&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Favorite Places") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.01) Loop Until AOLChildVis& = 1& Do: DoEvents AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) AddNew& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Add New Folder/Favorite Place") AddNewVis& = IsWindowVisible(AddNew&) Call Pause(0.25) Loop Until AddNewVis& = 1& AOLEdit& = FindWindowEx(AddNew&, 0&, "_AOL_Edit", vbNullString) AOLEdit& = FindWindowEx(AddNew&, AOLEdit&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Place$) AOLEdit& = FindWindowEx(AddNew&, AOLEdit&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Address$) AOLIcon& = FindWindowEx(AddNew&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AddNew&, AOLIcon&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AddNew& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Add New Folder/Favorite Place") Loop Until AddNew& = 0& Call PostMessage(AOLChild&, WM_CLOSE, 0&, 0&) End Sub Public Sub AddTree(hWnd As Long, Ctrl As Control, CheckForDupe As Boolean) ' This sub will add all of the items in a AOL Tree to a control of your choice, ' and can also check for duplicates. ' This example will add all of the items from AOLTree& to a listbox named ' List1 and will check for duplicates. ' AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) ' Call AddTree(AOLTree&, List1, True) Dim ListCount As Long, i As Long, TxtLength As Long, AOLTreeTxt As String ListCount& = SendMessage(hWnd&, LB_GETCOUNT, 0&, 0&) For i& = 0& To ListCount& - 1&: DoEvents TxtLength& = SendMessage(hWnd&, LB_GETTEXTLEN, i&, 0&) AOLTreeTxt$ = String(TxtLength& + 1&, 0&) Call SendMessageByString(hWnd&, LB_GETTEXT, IndexNum&, AOLTreeTxt$) If CheckForDupe = True Then For i& = 0& To Ctrl.ListCount - 1& If LCase(Ctrl.List(i&)) = LCase(AOLTreeTxt$) Then GoTo EndOfLoop Next i& Ctrl.AddItem AOLTreeTxt$ Else Ctrl.AddItem AOLTreeTxt$ End If EndOfLoop: Next i& End Sub Public Function AOLScreenname() As String ' This function extracts the user's AOL screenname. Here's an example: ' This example brings up a messagebox giving the user's screenname. ' MsgBox "Your AOL screenname is: " & AOLScreenname() Dim CaptionLength As Long, WelcomeWndCaption As String, UserScreenname As String CaptionLength& = GetWindowTextLength(FindWelcomeWnd()) WelcomeWndCaption$ = String$(CaptionLength&, 0&) Call GetWindowText(FindWelcomeWnd(), WelcomeWndCaption$, (CaptionLength& + 1&)) UserScreenname$ = Mid(WelcomeWndCaption$, 10&, Len(WelcomeWndCaption$)) AOLScreenname$ = Mid(UserScreenname$, 1&, Len(UserScreenname$) - 1&) End Function Public Sub BuddyChat(Screennames As String, Message As String, RoomName As String) ' This sub will send a buddy chat invitation. Here are some examples... ' This example will send a buddy chat invitation to one person. ' Call BuddyChat("Screenname", "Come chat with me!", "My Room") ' This example will send a buddy chat invitation to 3 people. ' Screennames$ = "Screenname1,Screenname2,Screenname3" ' Call BuddyChat(Screennames$, "Come chat with me!", "My Room") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLIcon As Long, BuddyChat As Long Dim BuddyChatVis As Long, AOLEdit As Long, i As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyChat& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy Chat") BuddyChatVis& = IsWindowVisible(BuddyChat&) Call Pause(0.1) Loop Until BuddyChatVis& = 1& AOLEdit& = FindWindowEx(BuddyChat&, 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screennames$) AOLEdit& = FindWindowEx(BuddyChat&, AOLEdit&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Message$) AOLEdit& = FindWindowEx(BuddyChat&, AOLEdit&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, RoomName$) AOLIcon& = FindWindowEx(BuddyChat&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub ChangeCaption(hWnd As Long, NewCaption As String) ' This sub will change the caption of the window you specify. ' This example will change the caption of AOL to "Blah Blah Blah". ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call ChangeCaption(AOLFrame&, "Blah Blah Blah") Call SendMessageByString(hWnd&, WM_SETTEXT, 0&, NewCaption$) End Sub Public Sub ChangeModemSpeakerVolume(Level As String) ' This sub will change the modem speaker volume to the level you specify. ' This example will turn the modem speaker off. ' Call ChangeModemSpeakerVolume("off") ' This example will turn the modem speaker volume to low. ' Call ChangeModemSpeakerVolue("low") ' This example will turn the modem speaker volume to normal. ' Call ChangeModemSpeakerVolue("normal") ' This example will turn the modem speaker volume to loud. ' Call ChangeModemSpeakerVolue("loud") Dim AOLFrame As Long, MDIClient As Long, SignOn As Long, Goodbye As Long Dim AOLIcon As Long, AOLModal As Long, AOLModVis As Long, AOLTabControl As Long Dim AOLTabPage As Long, AOLCombobox As Long, AOLChild As Long, AOLChildVis As Long, i As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") If SignOn& Then AOLChild& = SignOn&: If Goodbye& Then AOLChild& = Goodbye& If AOLChild& = 0& Then Exit Sub AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "AOL Setup") AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Connection Setup") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.3) Loop Until AOLChildVis& = 1& AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) Call PostMessage(AOLTabControl&, WM_KEYDOWN, VK_RIGHT, 0&) Call PostMessage(AOLTabControl&, WM_KEYUP, VK_RIGHT, 0&) Call Pause(0.1) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, AOLTabPage&, "_AOL_TabPage", vbNullString) AOLIcon& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon& = FindWindowEx(AOLTabPage&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call ClickIcon(AOLIcon&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "AOL Setup") AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLCombobox& = FindWindowEx(AOLModal&, 0&, "_AOL_Combobox", vbNullString) For i& = 1& To 2& AOLCombobox& = FindWindowEx(AOLModal&, AOLCombobox&, "_AOL_Combobox", vbNullString) Next i& Select Case LCase(Level$) Case "off": Do: DoEvents If SendMessageByNum(AOLCombobox&, CB_GETCURSEL, 0&, 0&) = 0& Then Exit Do Call SendMessage(AOLCombobox&, CB_SETCURSEL, 0&, 0&) Loop Case "low": Do: DoEvents If SendMessageByNum(AOLCombobox&, CB_GETCURSEL, 0&, 0&) = 1& Then Exit Do Call SendMessage(AOLCombobox&, CB_SETCURSEL, 1&, 0&) Loop Case "normal": Do: DoEvents If SendMessageByNum(AOLCombobox&, CB_GETCURSEL, 0&, 0&) = 2& Then Exit Do Call SendMessage(AOLCombobox&, CB_SETCURSEL, 2&, 0&) Loop Case "loud": Do: DoEvents If SendMessageByNum(AOLCombobox&, CB_GETCURSEL, 0&, 0&) = 3& Then Exit Do Call SendMessage(AOLCombobox&, CB_SETCURSEL, 3&, 0&) Loop End Select AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "AOL Setup") Loop Until AOLModal& = 0& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Connection Setup") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub ChangeProfile(YourName As String, CityStateCountry As String, Birthday As String, Sex As String, MaritalStatus As String, Hobbies As String, ComputersUsed As String, Occupation As String, PersonalQuote As String) ' This sub will change the user's profile to whatever you specify. Here's an example... ' Note: The value of Sex$ can only be "male", "female", or "noresponse". ' YourName$ = "John Doe" ' CityStateCountry$ = "Anytown, AnyState USA" ' Birthday$ = "99/99/99" ' Sex$ = "Male" ' MaritalStatus$ = "Single" ' Hobbies$ = "Sex, sex, and sex." ' ComputersUsed$ = "Who cares." ' Occupation$ = "Bomb specialist." ' PersonalQuote$ = "Suck me beautiful!" ' Call ChangeProfile(YourName$, CityStateCountry$, Birthday$, Sex$, MaritalStatus$, Hobbies$, ComputersUsed$, Occupation$, PersonalQuote$) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim AOLEdit As Long, AOLCheckbox As Long, CheckboxVal As Long, AOLIcon As Long Dim Confirm As Long, ConfirmVis As Long, Button As Long, i As Long Call RunPopupMenu(6&, 4&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Edit Your Online Profile") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, YourName$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, CityStateCountry$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Birthday$) Select Case Trim(LCase(Sex$)) Case "male": AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) Do: DoEvents CheckboxVal& = SendMessage(AOLCheckbox&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 1& Then Exit Do Call SendMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) Loop Case "female": AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Do: DoEvents CheckboxVal& = SendMessage(AOLCheckbox&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 1& Then Exit Do Call SendMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) Loop Case "noresponse" AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) For i& = 1& To 2& AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Next i& Do: DoEvents CheckboxVal& = SendMessage(AOLCheckbox&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 1& Then Exit Do Call SendMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) Loop End Select AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, MaritalStatus$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Hobbies$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, ComputersUsed$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Occupation$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, PersonalQuote$) Call Pause(0.1) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents Confirm& = FindWindow("#32770", vbNullString) ConfirmVis& = IsWindowVisible(Confirm&) Call Pause(0.1) Loop Until ConfirmVis& = 1& Button& = FindWindowEx(Confirm&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub ChatIgnoreByIndex(IndexNum As Long) ' This sub is used to ignore a screenname in the chatroom by their index ' in the chat list. This sub is used by other subs. ' This example will ignore index number 5 in the chatroom. ' Call ChatIgnoreByIndex(5&) Dim AOLListbox As Long, AOLChild As Long Dim AOLCheckbox As Long, CheckboxVal As Long AOLListbox& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) Call SendMessageByNum(AOLListbox&, LB_SETCURSEL, IndexNum&, 0&) Call PostMessage(AOLListbox&, WM_LBUTTONDBLCLK, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindInfoAboutWnd() AOLCheckbox& = FindWindowEx(FindInfoAboutWnd(), 0&, "_AOL_Checkbox", vbNullString) Do: DoEvents CheckboxVal& = SendMessage(AOLCheckbox&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 1& Then Exit Do Call SendMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) Loop Call PostMessage(FindInfoAboutWnd(), WM_CLOSE, 0&, 0&) End Sub Public Sub ChatIgnoreByScreenname(TheScreenname As String) ' This sub will ignore a screenname in the chatroom. ' This example will ignore "Screenname" in the chatroom. ' Call ChatIgnoreByScreenname("Screenname") Dim RoomList As Long, hProcess As Long, Index As Long Dim ItemData As Long, Dest As Long, Screenname As String Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next If Screenname$ = AOLScreenname() Then Exit Sub If FindChatWnd() = 0& Then Exit Sub RoomList& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(RoomList&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(RoomList&, LB_GETCOUNT, 0&, 0&) - 1& Screenname$ = String(4&, vbNullChar) ItemData& = SendMessage(RoomList&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Screenname$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Screenname$, 4&) Dest& = Dest& + 6& Screenname$ = String(16&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Screenname$, 16&, lpNumberOfBytesWritten&) Screenname$ = Left(Screenname$, InStr(Screenname$, vbNullChar) - 1&) If LCase(TheScreenname$) = LCase(Screenname$) Then Call ChatIgnoreByIndex(Index&): Exit For Next Index& Call CloseHandle(hProcess&) End Sub Public Function ChatLinkHTML(Name As String, URL As String) As String ' This sub will set up a hyperlink for the AOL chatroom. ' This example will send a link to "http://www.bofen.com" to the chatroom. ' Call SendToChat(ChatLinkHTML("www.bofen.com", "http://www.bofen.com")) ' This example puts the link into a message to send to the chatroom. ' MyMessage$ = "To visit the best site on the net, bofen.com, " & ChatLinkHTML("click here!", "http://www.bofen.com") ' Call SendToChat(MyMessage$) ChatLinkHTML$ = "< a href=" & Chr(34) & URL$ & Chr(34) & ">" & Name$ & "" End Function Public Sub ChatNow() ' This sub will enter the user into a lobby room. Here's an example... ' Call ChatNow Call RunPopupMenu(10&, 2&, False) End Sub Public Sub ChatUnIgnoreByIndex(IndexNum As Long) ' This sub is used to unignore a screenname in the chatroom by their index ' in the chat list. This sub is used by other subs. ' This example will unignore index number 5 in the chatroom. ' Call ChatUnIgnoreByIndex(5&) Dim AOLListbox As Long, AOLChild As Long Dim AOLCheckbox As Long, CheckboxVal As Long AOLListbox& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) Call SendMessageByNum(AOLListbox&, LB_SETCURSEL, IndexNum&, 0&) Call PostMessage(AOLListbox&, WM_LBUTTONDBLCLK, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindInfoAboutWnd() AOLCheckbox& = FindWindowEx(FindInfoAboutWnd(), 0&, "_AOL_Checkbox", vbNullString) Do: DoEvents CheckboxVal& = SendMessage(AOLCheckbox&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 0& Then Exit Do Call SendMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) Loop Call PostMessage(FindInfoAboutWnd(), WM_CLOSE, 0&, 0&) End Sub Public Sub ChatUnIgnoreByScreenname(TheScreenname As String) ' This sub will unignore a screenname in the chatroom. ' This example will unignore "Screenname" in the chatroom. ' Call ChatUnIgnoreByScreenname("Screenname") Dim RoomList As Long, hProcess As Long, Index As Long Dim ItemData As Long, Dest As Long, Screenname As String Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next If Screenname$ = AOLScreenname() Then Exit Sub If FindChatWnd() = 0& Then Exit Sub RoomList& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(RoomList&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(RoomList&, LB_GETCOUNT, 0&, 0&) - 1& Screenname$ = String(4&, vbNullChar) ItemData& = SendMessage(RoomList&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Screenname$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Screenname$, 4&) Dest& = Dest& + 6& Screenname$ = String(16&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Screenname$, 16&, lpNumberOfBytesWritten&) Screenname$ = Left(Screenname$, InStr(Screenname$, vbNullChar) - 1&) If LCase(TheScreenname$) = LCase(Screenname$) Then Call ChatUnIgnoreByIndex(Index&): Exit For Next Index& Call CloseHandle(hProcess&) End Sub Public Function CheckIfAlive(Screenname As String) As Boolean ' This sub will check if a screenname is still a valid on AOL. Here's an example... ' Screenname$ = "JohnDoe123" ' If CheckIfAlive(Screenname$) = True Then ' MsgBox Screenname$ & " is a valid screenname." ' Else ' MsgBox Screenname$ & " is not a valid screenname." ' End If Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLView As Long, TextLen As Long Dim AOLIcon As Long, WriteMail As Long, SavePrompt As Long Dim SavePromptVis As Long, Button As Long, SNAlive As Boolean Dim AOLViewTxt As String Call SendMail("'," & Screenname$, " ", " ") AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Error") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) TextLen& = SendMessage(AOLView&, WM_GETTEXTLENGTH, 0&, 0&) AOLViewTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLView&, WM_GETTEXT, TextLen& + 1&, AOLViewTxt$) If InStr(AOLViewTxt$, LCase(ReplaceText(Screenname$, " ", ""))) Then If InStr(AOLViewTxt$, "mailbox") Then SNAlive = True Else SNAlive = False End If Else SNAlive = True End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Error") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 0& WriteMail& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Write Mail") Call PostMessage(WriteMail&, WM_CLOSE, 0&, 0&) Do: DoEvents SavePrompt& = FindWindow("#32770", vbNullString) SavePromptVis& = IsWindowVisible(SavePrompt&) Call Pause(0.1) Loop Until SavePromptVis& = 1& Button& = FindWindowEx(SavePrompt&, 0&, "Button", vbNullString) Button& = FindWindowEx(SavePrompt&, Button&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) CheckIfAlive = SNAlive End Function Public Function CheckIfMaster() As Boolean ' This sub will check to see if the user's screenname is a master ' screenname. Here's an example... ' If CheckIfMaster() = True Then ' MsgBox "This is a master screenname." ' Else ' MsgBox "This is not a master screenname." ' End If Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLIcon As Long, ErrorBox As Long Dim ErrorBoxVis As Long, Button As Long, IsMaster As Boolean Call RunPopupMenu(6&, 7&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", " AOL Parental Controls") AOLChildVis& = IsWindowVisible(AOLChild&) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ErrorBox& = FindWindow("#32770", "America Online") ErrorBoxVis& = IsWindowVisible(ErrorBox&) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Parental Controls") AOLChildVis& = IsWindowVisible(AOLChild&) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until ErrorBoxVis& = 1& Or AOLChildVis& = 1& If ErrorBoxVis& = 1& Then Button& = FindWindowEx(ErrorBox&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ErrorBox& = FindWindow("#32770", "America Online") Loop Until ErrorBox& = 0& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", " AOL Parental Controls") Call CloseWindow(AOLChild&) IsMaster = False Else Call CloseWindow(AOLChild&) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Parental Controls") Loop Until AOLChild& = 0& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", " AOL Parental Controls") Call CloseWindow(AOLChild&) IsMaster = True End If CheckIfMaster = IsMaster End Function Public Sub ClearChatWindow() ' This sub will clear the chat window. Here's an example... ' Call ClearChatWindow Call SendMessageByString(FindWindowEx(FindChatWnd(), 0&, "RICHCNTL", vbNullString), WM_SETTEXT, 0&, vbNullChar) End Sub Public Sub ClearHistory() ' This sub will clear the history of your AOL's keyword combo box. ' Here's an example on how to call this sub. ' Call ClearHistory Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, TextLen As Long Dim AOLChildVis As Long, AOLIcon As Long, AOLModal As Long Dim AOLModalVis As Long, ConfirmModal As Long, AOLStatic As Long Dim AOLStaticTxt As String Call RunPopupMenu(6&, 3&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Preferences") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Toolbar Preferences") AOLModalVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModalVis& = 1& AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ConfirmModal& = FindWindow("_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(ConfirmModal&, 0&, "_AOL_Static", vbNullString) TextLen& = SendMessage(AOLStatic&, WM_GETTEXTLENGTH, 0&, 0&) AOLStaticTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLStatic&, WM_GETTEXT, TextLen& + 1&, AOLStaticTxt$) Call Pause(0.1) Loop Until InStr(AOLStaticTxt$, "Do you want to continue?") AOLIcon& = FindWindowEx(ConfirmModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ConfirmModal& = FindWindow("_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(ConfirmModal&, 0&, "_AOL_Static", vbNullString) TextLen& = SendMessage(AOLStatic&, WM_GETTEXTLENGTH, 0&, 0&) AOLStaticTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLStatic&, WM_GETTEXT, TextLen& + 1&, AOLStaticTxt$) Call Pause(0.1) Loop Until InStr(AOLStaticTxt$, "Do you want to continue?") = 0& AOLModal& = FindWindow("_AOL_Modal", "Toolbar Preferences") AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Toolbar Preferences") AOLModalVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModal& = 0& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Preferences") Call PostMessage(AOLChild&, WM_CLOSE, 0&, 0&) End Sub Public Sub ClickIcon(AOLIcon As Long) ' This sub will click an icon. Here's an example... ' AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) ' Call ClickIcon(AOLIcon&) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub ClickRadioButton(hWnd As Long) ' This sub will click a radio button and makes its value true. Here's an example... ' AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) ' Call ClickRadioButton(AOLIcon&) Dim CheckboxVal As Long Do: DoEvents CheckboxVal& = SendMessage(hWnd&, BM_GETCHECK, 0&, 0&) If CheckboxVal& = 1& Then Exit Do Call SendMessage(hWnd&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(hWnd&, WM_LBUTTONUP, 0&, 0&) Loop End Sub Public Sub CloseWindow(hWnd As Long) ' This sub will close a window. ' This example will close an AOL Child. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) ' Call CloseWindow(AOLChild&) Call PostMessage(hWnd&, WM_CLOSE, 0&, 0&) End Sub Public Sub CollectScreennames(Ctrl As Control, Amount As Long, CheckForDupe As Boolean) ' This sub will collect however many screennames you specify from ' Who's Chatting, but make sure you don't set Amount& too high, ' because has rate limits on how many Who's Chatting windows appear. ' You can also have the sub check for duplicates. ' This sub will collect 100 screennames and will add them to a listbox ' named List1 and will check for duplicates. ' Call CollectScreennames(List1, 100&, True) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, Index As Long Dim AOLListbox As Long, ListboxCount As Long, AOLIcon As Long, i As Long Dim WhosChatting As Long, WhosChattingVis As Long, TempNum As Long Dim WhosChattingListbox As Long, WhosChattingListboxCount As Long, k As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Find a Chat") If AOLChild& = 0& Then Call RunPopupMenu(10&, 3&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Find a Chat") AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call Pause(2) Loop Until AOLChild& And AOLListbox& End If AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, AOLListbox&, "_AOL_Listbox", vbNullString) ListboxCount& = GetListCount(AOLListbox&) For i& = 0& To ListboxCount& - 1&: DoEvents Call SelectItemFromListbox(AOLListbox&, i&) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For k& = 1& To 8& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next k& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents WhosChatting& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Who's Chatting") WhosChattingVis& = IsWindowVisible(WhosChatting&) Call Pause(0.2) Loop Until WhosChattingVis& = 1& WhosChattingListbox& = FindWindowEx(WhosChatting&, 0&, "_AOL_Listbox", vbNullString) WhosChattingListboxCount& = WhosChattingListboxCount& + GetListCount(WhosChattingListbox&) Call WaitForListToLoad(WhosChattingListbox&) Call AddListbox(WhosChattingListbox&, Ctrl, CheckForDupe) Do: DoEvents WhosChatting& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Who's Chatting") Call CloseWindow(WhosChatting&) Call Pause(0.1) Loop Until WhosChatting& = 0& If WhosChattingListboxCount& >= Amount& Then TempNum& = WhosChattingListboxCount& - Amount& For Index& = 1& To TempNum& Ctrl.RemoveItem (Ctrl.ListCount - 1&) Next Index& Exit For End If Next i& Call CloseWindow(FindWindowEx(MDIClient&, 0&, "AOL Child", "Find a Chat")) End Sub Public Function ConvertListToString(List As ListBox) As String ' This function will convert all the items in a listbox into a string. ' This example will put the list (List1) into a string called MyString$. ' MyString$ = ConvertListToString(List1) Dim i As Long, strString As String For i& = 0& To List.ListCount - 1& If i& = (List.ListCount - 1&) Then strString$ = strString$ & List.List(i&) Else strString$ = strString$ & List.List(i&) & Chr(13) & Chr(10) End If Next i& ConvertListToString$ = strString$ End Function Public Sub ConvertStringToList(Text As String, List As ListBox) ' This sub will add all the lines from a string into a listbox. ' This example will add all the lines from MyString$ into a listbox named List1. ' MyString$ = "Item1" & Chr(13) & Chr(10) & "Item2" & Chr(13) & Chr(10) & "Item3" ' Call ConvertStringToList(MyString$, List1) If GetLineCount(Text$) = 0& Then Exit Sub For i& = 1& To GetLineCount(Text$): DoEvents List.AddItem GetLineFromText(Text$, i&) Next i& End Sub Public Sub CopyFile(File As String, NewFile As String) ' This sub will copy a file. ' This example will copy "C:\MyFile.txt" to "C:\MyFolder\MyFile.txt". ' Call CopyFile("C:\MyFile.txt", "C:\MyFolder\MyFile.txt") Call FileCopy(File$, NewFile$) End Sub Public Function CountFlashMail() As Long ' This function will count and return the number of mails in your ' flashmail mailbox. Here's an example: ' MsgBox "You have " & CountFlashMail() & " mails in your flashmail mailbox." Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") If AOLChild& = 0& Then Call OpenFlashMail AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) CountFlashMail& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) End Function Public Function CountNewMail() As Long ' This function will count and return the number of mails in your ' new mail mailbox. Here's an example: ' MsgBox "You have " & CountNewMail() & " mails in your new mail mailbox." Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim ListCount1 As Long, ListCount2 As Long, ListCount3 As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") If AOLChild& = 0& Then Call OpenNewMail AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) CountNewMail& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) End Function Public Sub CreateBuddyGroup(GroupName As String) ' This sub will create a new buddy group. The following example ' will create a buddy group named "My Buddies". ' Call CreateBuddyGroup("My Buddies") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, i As Long Dim AOLIcon As Long, AOLListbox As Long, BuddyLists As Long Dim BuddyListsVis As Long, CreateBuddyWnd As Long, AOLEdit As Long Dim CreateBuddyWndVis As Long, FirstCount As Long, SecondCount As Long Dim MsgErr As Long, MsgErrVis As Long, Button As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) If FindCreateBuddyGroupWnd() = 0& Then AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLIcon& And AOLListbox& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& AOLListbox& = FindWindowEx(BuddyLists&, 0&, "_AOL_Listbox", vbNullString) If IsItemInListbox(AOLListbox&, GroupName$) Then BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call CloseWindow(BuddyLists&) Exit Sub End If AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents CreateBuddyWnd& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Create a Buddy List Group") CreateBuddyWndVis& = IsWindowVisible(CreateBuddyWnd&) Call Pause(0.1) Loop Until CreateBuddyWndVis& = 1& End If CreateBuddyWnd& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Create a Buddy List Group") AOLListbox& = FindWindowEx(CreateBuddyWnd&, 0&, "_AOL_Listbox", vbNullString) FirstCount& = GetListCount(AOLListbox&) AOLEdit& = FindWindowEx(CreateBuddyWnd&, 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, GroupName$) AOLIcon& = FindWindowEx(CreateBuddyWnd&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(CreateBuddyWnd&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgErr& = FindWindow("#32770", "America Online") MsgErrVis& = IsWindowVisible(MsgErr&) Call Pause(0.1) Loop Until MsgErrVis& = 1& MsgErr& = FindWindow("#32770", "America Online") Button& = FindWindowEx(MsgErr&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgErr& = FindWindow("#32770", "America Online") Call Pause(0.1) Loop Until MsgErr& = 0& Do: DoEvents CreateBuddyWnd& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") AOLListbox& = FindWindowEx(CreateBuddyWnd&, 0&, "_AOL_Listbox", vbNullString) SecondCount& = GetListCount(AOLListbox&) Call Pause(0.1) Loop Until SecondCount& > FirstCount& BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call CloseWindow(BuddyLists&) End Sub Public Sub DeleteBuddyGroup(GroupName As String) ' This sub will delete a buddy group. The following will delete ' the buddy group named "My Buddies". ' Call DeleteBuddyGroup("My Buddies") Dim AOLFrame As Long, MDIClient As Long, BuddyLists As Long Dim AOLChild As Long, AOLIcon As Long, AOLListbox As Long, i As Long Dim BuddyListsVis As Long, hProcess As Long, lpdwProcessId As Long Dim AOLModVis As Long, Index As Long, Item As String, ItemData As Long Dim lpNumberOfBytesWritten As Long, Dest As Long, AOLModal As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") If BuddyLists& = 0& Then AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLIcon& And AOLListbox& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& End If BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") AOLListbox& = FindWindowEx(BuddyLists&, 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(AOLListbox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLListbox&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLListbox&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Left(Item$, InStr(Item$, vbNullChar) - 1&) If Trim(LCase(Mid(Item$, 1&, Len(GroupName$)))) = LCase(Trim(GroupName$)) Then Call SelectItemFromListbox(AOLListbox&, Index&): Exit For Next Index& Call CloseHandle(hProcess&) BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(BuddyLists&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) Call Pause(0.1) Loop Until AOLModal& = 0& Call CloseWindow(FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists")) End Sub Public Function DirectoryExists(DirectoryPath As String) As Boolean ' This function will check if the directory you specify exits on ' the user's computer. ' This example will check to see if the folder "C:\MyFolder" exists ' on the user's computer and will bring up a message box stating ' the folders condition. ' TheFolder$ = "C:\MyFolder" ' If DirectoryExists(TheFolder$) Then ' MsgBox TheFolder$ & " exists on this computer." ' Else ' MsgBox TheFolder$ & " does not exist on this computer." ' End If If Len(Trim(DirectoryPath$)) = 0& Then DirectoryExists = False: Exit Function If Len(Dir(DirectoryPath, vbDirectory)) Then DirectoryExists = True Else DirectoryExists = False End If End Function Public Sub DisableWnd(hWnd As Long) ' This sub will disable a window. The following example will disable ' AOL's MDI Client form... ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' Call DisableWindow(MDIClient&) Call EnableWindow(hWnd&, False) End Sub Public Sub DownloadLater(Mailbox As String, MailIndex As Long) ' This sub will put either a flash mail or new mail into the Download ' Manager on AOL, depending on which you choose. ' Note: Mailbox$ can only have the value of "flashmail" or "newmail". ' This example will put a mail from your flashmail mailbox with index ' number 5 into the Download Manager. ' Call DownloadLater("flashmail", 5&) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim AOLIcon As Long, ReadWndVis As Long, AOLModal As Long Dim ErrorWnd As Long, ErrorWndVis As Long, Button As Long, i As Long Dim AOLTabControl As Long, AOLTabPage As Long, AOLModVis As Long Select Case Trim(LCase(Mailbox$)) Case "flashmail": AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") If AOLChild& = 0& Then Call OpenNewMail AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) Call SendMessageByNum(AOLTree&, LB_SETCURSEL, MailIndex&, 0&) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ReadWndVis& = IsWindowVisible(FindReadWnd()) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until ReadWndVis& = 1& AOLIcon& = FindWindowEx(FindReadWnd(), 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(FindReadWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLModVis& = IsWindowVisible(AOLModal&) ErrorWnd& = FindWindow("#32770", vbNullString) ErrorWndVis& = IsWindowVisible(ErrorWnd&) Call Pause(0.1) Loop Until AOLModVis& = 1& Or ErrorWndVis& = 1& If ErrorWndVis& = 1& Then ErrorWnd& = FindWindow("#32770", vbNullString) Button& = FindWindowEx(ErrorWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ErrorWnd& = FindWindow("#32770", vbNullString) ErrorWndVis& = IsWindowVisible(ErrorWnd&) Call Pause(0.1) Loop Until ErrorWndVis& = 0& Else AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) Call Pause(0.1) Loop Until AOLModal& = 0& End If Do: DoEvents Call CloseWindow(FindReadWnd()) Call Pause(0.1) Loop Until FindReadWnd() = 0& Case "newmail": AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) If AOLChild& = 0& Then Call OpenFlashMail AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTree& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Tree", vbNullString) Call SendMessageByNum(AOLTree&, LB_SETCURSEL, MailIndex&, 0&) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ReadWndVis& = IsWindowVisible(FindReadWnd()) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until ReadWndVis& = 1& AOLIcon& = FindWindowEx(FindReadWnd(), 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(FindReadWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLModVis& = IsWindowVisible(AOLModal&) ErrorWnd& = FindWindow("#32770", vbNullString) ErrorWndVis& = IsWindowVisible(ErrorWnd&) Call Pause(0.1) Loop Until AOLModVis& = 1& Or ErrorWndVis& = 1& If ErrorWndVis& = 1& Then ErrorWnd& = FindWindow("#32770", vbNullString) Button& = FindWindowEx(ErrorWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ErrorWnd& = FindWindow("#32770", vbNullString) ErrorWndVis& = IsWindowVisible(ErrorWnd&) Call Pause(0.1) Loop Until ErrorWndVis& = 0& Else AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) Call Pause(0.1) Loop Until AOLModal& = 0& End If Do: DoEvents Call CloseWindow(FindReadWnd()) Call Pause(0.1) Loop Until FindReadWnd() = 0& AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call Pause(0.3) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Select End Sub Public Sub EditAOLShortCuts(KeyNum As Long, Title As String, Address As String) ' This sub will add Title$ to your AOL ShortCuts. AOL allows 10 shortcuts, ' KeyNum& is the number of the shortcut you want to edit. ' This example will edit shortcut number 1 (it will add the address "http://www.bofen.com" ' with the title "b o f e n . c o m"). ' Call EditAOLShortCuts(1&, "b o f e n . c o m", "http://www.bofen.com") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim FirstEdit As Long, SecondEdit As Long, AOLIcon As Long, i As Long Call RunPopupMenu(7&, 4&, True, 1&) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Edit Shortcut Keys") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.01) Loop Until AOLChildVis& = 1& If KeyNum& = 1& Then FirstEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) SecondEdit& = FindWindowEx(AOLChild&, FirstEdit&, "_AOL_Edit", vbNullString) Else FirstEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) For i& = 1& To KeyNum& - 1& FirstEdit& = FindWindowEx(AOLChild&, FirstEdit&, "_AOL_Edit", vbNullString) FirstEdit& = FindWindowEx(AOLChild&, FirstEdit&, "_AOL_Edit", vbNullString) Next i& SecondEdit& = FindWindowEx(AOLChild&, FirstEdit&, "_AOL_Edit", vbNullString) End If Call SendMessageByString(FirstEdit&, WM_SETTEXT, 0&, Title$) Call SendMessageByString(SecondEdit&, WM_SETTEXT, 0&, Address$) Do: DoEvents AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Edit Shortcut Keys") Call Pause(0.25) Loop Until AOLChild& = 0& End Sub Public Sub EnableWnd(hWnd As Long) ' This sub will enable a window. The following example will enable ' AOL's MDI Client form... ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' Call EnableWindow(MDIClient&) Call EnableWindow(hWnd&, True) End Sub Public Sub EnterPrivateRoom(Room As String) ' This sub will enter the user to a private room. The following ' example will enter the user to the private room "games". ' Call EnterPrivateRoom("games") Call Keyword("aol://2719:2-2-" & Room$) End Sub Public Function ExtractErrorNames(CloseErrorWnd As Boolean) As String ' This function will return the names from the "mail error" window. You can ' also have the function close the error window by setting CloseErrorWnd to ' True. ' In this example, ErrorNames$ will contain all of the names with errors and ' the function will close the "mail error" window. ' ErrorNames$ = ExtractErrorNames(True) ' Note: You may want to use the GetLineCount and GetLineFromText ' functions to extract the error names from the string. Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLView As Long, AOLIcon As Long, i As Long, ErrorNames As String Dim ErrorLine As String, Screenname As String, ErrorMsg As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Error") If AOLChild& = 0& Then Exit Function AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) ErrorMsg$ = GetText(AOLView&) For i& = 3& To GetLineCount(ErrorMsg$) ErrorLine$ = GetLineFromText(ErrorMsg$, i&) Screenname$ = Left(ErrorLine$, InStr(ErrorLine$, " - ") - 1&) If i& = GetLineCount(ErrorMsg$) Then ErrorNames$ = ErrorNames$ & Screenname$ Else ErrorNames$ = ErrorNames$ & Screenname$ & Chr(13) & Chr(10) End If Next i& If CloseErrorWnd = True Then Do: DoEvents AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call ClickIcon(AOLIcon&) Call Pause(0.1) Loop Until AOLChild& = 0& End If ExtractErrorNames$ = ErrorNames$ End Function Public Function FileExists(FilePath As String) As Boolean ' This function will check if the file you specify exits on ' the user's computer. ' This example will check to see if the file "C:\MyFile.txt" exists ' on the user's computer and will bring up a message box stating ' the folders condition. ' TheFile$ = "C:\MyFile.txt" ' If DirectoryExists(TheFile$) Then ' MsgBox TheFile$ & " exists on this computer." ' Else ' MsgBox TheFile$ & " does not exist on this computer." ' End If If Len(Trim(FileName$)) = 0& Then FileExists = False: Exit Function If Len(Dir(FilePath$)) Then FileExists = True Else FileExists = False End If End Function Public Function FindAIMAcceptWnd() As Long ' This function finds the AIM acceptance window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the AIM acceptance window is found. ' If FindAIMAcceptWnd() <> 0& Then MsgBox "AIM acceptance window found!" ' or ' If FindAIMAcceptWnd() Then MsgBox "AIM acceptance window found!" ' This example will return the AIM acceptance window's handle if its found. ' If FindAIMAcceptWnd() <> 0& Then MsgBox FindAIMAcceptWnd() ' or ' If FindAIMAcceptWnd() Then MsgBox FindAIMAcceptWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLEdit As Long, AOLStatic As Long, AOLIcon As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Do While (Counter& <> 100&) And (AOLEdit& = 0& Or AOLStatic& = 0& Or AOLIcon& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& If AOLEdit& And AOLStatic& And AOLIcon& And InStr(GetText(AOLStatic&), "Would you like to accept?") Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindAIMAcceptWnd& = AOLChild& Exit Function End If End Function Public Function FindCreateBuddyGroupWnd() As Long ' This function finds the Create Buddy Group window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Create Buddy Group window is found. ' If FindCreateBuddyGroupWnd() <> 0& Then MsgBox "Create Buddy Group window found!" ' or ' If FindCreateBuddyGroupWnd() Then MsgBox "Create Buddy Group window found!" ' This example will return the Create Buddy Group window's handle if its found. ' If FindCreateBuddyGroupWnd() <> 0& Then MsgBox FindCreateBuddyGroupWnd() ' or ' If FindCreateBuddyGroupWnd() Then MsgBox FindCreateBuddyGroupWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLStatic As Long Dim AOLEdit As Long, AOLGlyph As Long, AOLStatic2 As Long, AOLEdit2 As Long Dim AOLIcon As Long, AOLStatic3 As Long, AOLListbox As Long, AOLIcon2 As Long Dim AOLGlyph2 As Long, AOLIcon3 As Long, i As Long, Counter As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) For i& = 1& To 2& AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) Next i& AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLGlyph2& = FindWindowEx(AOLChild&, AOLGlyph&, "_AOL_Glyph", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLEdit& = 0& Or AOLGlyph& = 0& Or AOLStatic2& = 0& Or AOLEdit2& = 0& Or AOLIcon& = 0& Or AOLStatic3& = 0& Or AOLListbox& = 0& Or AOLIcon2& = 0& Or AOLGlyph2& = 0& Or AOLIcon3& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) For i& = 1& To 2& AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) Next i& AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLGlyph2& = FindWindowEx(AOLChild&, AOLGlyph&, "_AOL_Glyph", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& If AOLStatic& And AOLEdit& And AOLGlyph& And AOLStatic2& And AOLEdit2& And AOLIcon& And AOLStatic3& And AOLListbox& And AOLIcon2& And AOLGlyph2& And AOLIcon3& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindCreateBuddyGroupWnd& = AOLChild& Exit Function End If End Function Public Function FindChatWnd() As Long ' This function finds the chatroom window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the chatroom window is found. ' If FindChatWnd() <> 0& Then MsgBox "Chatroom window found!" ' or ' If FindChatWnd() Then MsgBox "Chatroom window found!" ' This example will return the chatroom window's handle if its found. ' If FindChatWnd() <> 0& Then MsgBox FindChatWnd() ' or ' If FindChatWnd() Then MsgBox FindChatWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLStatic As Long Dim RICHCNTL As Long, AOLCombobox As Long, AOLIcon As Long, AOLStatic2 As Long Dim RICHCNTL2 As Long, AOLIcon2 As Long, AOLImage As Long, AOLStatic3 As Long Dim AOLListbox As Long, AOLStatic4 As Long, AOLIcon3 As Long, i As Long, Counter As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& AOLImage& = FindWindowEx(AOLChild&, 0&, "_AOL_Image", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 6& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& Do While (Counter& <> 100&) And (AOLStatic& = 0& Or RICHCNTL& = 0& Or AOLCombobox& = 0& Or AOLIcon& = 0& Or AOLStatic2& = 0& Or RICHCNTL2& = 0& Or AOLIcon2& = 0& Or AOLImage& = 0& Or AOLStatic3& = 0& Or AOLListbox& = 0& Or AOLStatic4& = 0& Or AOLIcon3& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& AOLImage& = FindWindowEx(AOLChild&, 0&, "_AOL_Image", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 6& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& If AOLStatic& And RICHCNTL& And AOLCombobox& And AOLIcon& And AOLStatic2& And RICHCNTL2& And AOLIcon2& And AOLImage& And AOLStatic3& And AOLListbox& And AOLStatic4& And AOLIcon3& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindChatWnd& = AOLChild& Exit Function End If End Function Public Function FindEditBuddyWnd() As Long ' This function finds the Edit Buddy window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Edit Buddy window is found. ' If FindEditBuddyWnd() <> 0& Then MsgBox "Edit Buddy window found!" ' or ' If FindEditBuddyWnd() Then MsgBox "Edit Buddy window found!" ' This example will return the Edit Buddy window's handle if its found. ' If FindEditBuddyWnd() <> 0& Then MsgBox FindEditBuddyWnd() ' or ' If FindEditBuddyWnd() Then MsgBox FindEditBuddyWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLStatic As Long Dim AOLCombobox As Long, AOLStatic2 As Long, AOLEdit As Long, AOLGlyph As Long Dim AOLStatic3 As Long, AOLEdit2 As Long, AOLIcon As Long, AOLStatic4 As Long Dim AOLListbox As Long, AOLIcon2 As Long, AOLIcon3 As Long Dim AOLGlyph2 As Long, Counter As Long, i As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLGlyph2& = FindWindowEx(AOLChild&, AOLGlyph&, "_AOL_Glyph", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLCombobox& = 0& Or AOLStatic2& = 0& Or AOLEdit& = 0& Or AOLGlyph& = 0& Or AOLStatic3& = 0& Or AOLEdit2& = 0& Or AOLIcon& = 0& Or AOLStatic4& = 0& Or AOLListbox& = 0& Or AOLIcon2& = 0& Or AOLGlyph2& = 0& Or AOLIcon3& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLGlyph2& = FindWindowEx(AOLChild&, AOLGlyph&, "_AOL_Glyph", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) Next i& If AOLStatic& And AOLCombobox& And AOLStatic2& And AOLEdit& And AOLGlyph& And AOLStatic3& And AOLEdit2& And AOLIcon& And AOLStatic4& And AOLListbox& And AOLIcon2& And AOLGlyph2& And AOLIcon3& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindEditBuddyWnd& = AOLChild& Exit Function End If End Function Public Function FindForwardWnd() As Long ' This function finds the mail forward window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the mail forward window is found. ' If FindForwardWnd() <> 0& Then MsgBox "Mail forward window found!" ' or ' If FindForwardWnd() Then MsgBox "Mail forward window found!" ' This example will return the mail forward window's handle if its found. ' If FindForwardWnd() <> 0& Then MsgBox FindForwardWnd() ' or ' If FindForwardWnd() Then MsgBox FindForwardWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLStatic As Long Dim AOLEdit As Long, AOLStatic2 As Long, AOLEdit2 As Long, AOLStatic3 As Long, Counter As Long Dim AOLEdit3 As Long, AOLFontCombo As Long, AOLStatic4 As Long, AOLCombobox As Long Dim AOLIcon As Long, RICHCNTL As Long, AOLCheckbox As Long, AOLStatic5 As Long, i As Long Dim AOLIcon2 As Long, AOLStatic6 As Long, AOLIcon3 As Long, AOLStatic7 As Long, AOLIcon4 As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLEdit3& = FindWindowEx(AOLChild&, AOLEdit2&, "_AOL_Edit", vbNullString) AOLFontCombo& = FindWindowEx(AOLChild&, 0&, "_AOL_FontCombo", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 10& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) AOLStatic5& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLStatic6& = FindWindowEx(AOLChild&, AOLStatic5&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic7& = FindWindowEx(AOLChild&, AOLStatic6&, "_AOL_Static", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLEdit& = 0& Or AOLStatic2& = 0& Or AOLEdit2& = 0& Or AOLStatic3& = 0& Or AOLEdit3& = 0& Or AOLFontCombo& = 0& Or AOLStatic4& = 0& Or AOLCombobox& = 0& Or AOLIcon& = 0& Or RICHCNTL& = 0& Or AOLCheckbox& = 0& Or AOLStatic5& = 0& Or AOLIcon2& = 0& Or AOLStatic6& = 0& Or AOLIcon3& = 0& Or AOLStatic7& = 0& Or AOLIcon4& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLEdit3& = FindWindowEx(AOLChild&, AOLEdit2&, "_AOL_Edit", vbNullString) AOLFontCombo& = FindWindowEx(AOLChild&, 0&, "_AOL_FontCombo", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 10& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) AOLStatic5& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLStatic6& = FindWindowEx(AOLChild&, AOLStatic5&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic7& = FindWindowEx(AOLChild&, AOLStatic6&, "_AOL_Static", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) If AOLStatic& And AOLEdit& And AOLStatic2& And AOLEdit2& And AOLStatic3& And AOLEdit3& And AOLFontCombo& And AOLStatic4& And AOLCombobox& And AOLIcon& And RICHCNTL& And AOLCheckbox& And AOLStatic5& And AOLIcon2& And AOLStatic6& And AOLIcon3& And AOLStatic7& And AOLIcon4& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindForwardWnd& = AOLChild& Exit Function End If End Function Public Function FindGuestWnd() As Long ' This function finds the Guest Sign-On window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Guest Sign-On window is found. ' If FindGuestWnd() <> 0& Then MsgBox "Guest Sign-On window found!" ' or ' If FindGuestWnd() Then MsgBox "Guest Sign-On window found!" ' This example will return the Guest Sign-On window's handle if its found. ' If FindGuestWnd() <> 0& Then MsgBox FindGuestWnd() ' or ' If FindGuestWnd() Then MsgBox FindGuestWnd() Dim AOLModal As Long, AOLStatic As Long, AOLEdit As Long Dim AOLStatic2 As Long, AOLEdit2 As Long, AOLStatic3 As Long Dim AOLIcon As Long, Counter As Long, i As Long AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, 0&, "_AOL_Static", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLModal&, 0&, "_AOL_Edit", vbNullString) AOLStatic2& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLModal&, AOLEdit&, "_AOL_Edit", vbNullString) AOLStatic3& = FindWindowEx(AOLModal&, AOLStatic2&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, AOLIcon&, "_AOL_Icon", vbNullString) Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLEdit& = 0& Or AOLStatic2& = 0& Or AOLEdit2& = 0& Or AOLStatic3& = 0& Or AOLIcon& = 0&): DoEvents AOLModal& = FindWindowEx(AOLModal&, AOLModal&, "_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, 0&, "_AOL_Static", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit& = FindWindowEx(AOLModal&, 0&, "_AOL_Edit", vbNullString) AOLStatic2& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLEdit2& = FindWindowEx(AOLModal&, AOLEdit&, "_AOL_Edit", vbNullString) AOLStatic3& = FindWindowEx(AOLModal&, AOLStatic2&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLModal&, AOLIcon&, "_AOL_Icon", vbNullString) If AOLStatic& And AOLEdit& And AOLStatic2& And AOLEdit2& And AOLStatic3& And AOLIcon& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindGuestWnd& = AOLModal& Exit Function End If End Function Public Function FindInfoAboutWnd() As Long ' This function finds the Info About window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' Note: The Info About window is the window that appears after you ' double-click a screenname in the chatroom list. ' This example will bring up a message box if the Info About window is found. ' If FindInfoAboutWnd() <> 0& Then MsgBox "Info About window found!" ' or ' If FindInfoAboutWnd() Then MsgBox "Info About window found!" ' This example will return the Info About window's handle if its found. ' If FindInfoAboutWnd() <> 0& Then MsgBox FindInfoAboutWnd() ' or ' If FindInfoAboutWnd() Then MsgBox FindInfoAboutWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLStatic As Long Dim AOLCheckbox As Long, AOLGlyph As Long, AOLIcon As Long, Counter As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLCheckbox& = 0& Or AOLGlyph& = 0& Or AOLIcon& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) AOLGlyph& = FindWindowEx(AOLChild&, 0&, "_AOL_Glyph", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) If AOLStatic& And AOLCheckbox& And AOLGlyph& And AOLIcon& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindInfoAboutWnd& = AOLChild& Exit Function End If End Function Public Function FindInstantMessageWnd() As Long ' This function finds the Instant Message window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Instant Message window is found. ' If FindInstantMessageWnd() <> 0& Then MsgBox "Instant Message window found!" ' or ' If FindInstantMessageWnd() Then MsgBox "Instant Message window found!" ' This example will return the Instant Message window's handle if its found. ' If FindInstantMessageWnd() <> 0& Then MsgBox FindInstantMessageWnd() ' or ' If FindInstantMessageWnd() Then MsgBox FindInstantMessageWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, Counter As Long Dim AOLView As Long, AOLStatic As Long, RICHCNTL As Long, i As Long Dim AOLIcon As Long, RICHCNTL2 As Long, AOLIcon2 As Long, AOLStatic2 As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) AOLView& = FindWindowEx(AOLChild&, AOLView&, "_AOL_View", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) For i& = 1& To 2& AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 7& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 5& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) Do While (Counter& <> 100&) And (AOLView& = 0& Or AOLStatic& = 0& Or RICHCNTL& = 0& Or AOLIcon& = 0& Or RICHCNTL2& = 0& Or AOLIcon2& = 0& Or AOLStatic2& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) AOLView& = FindWindowEx(AOLChild&, AOLView&, "_AOL_View", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) For i& = 1& To 2& AOLStatic& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 7& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 5& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) If AOLView& And AOLStatic& And RICHCNTL& And AOLIcon& And RICHCNTL2& And AOLIcon2& And AOLStatic2& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindInstantMessageWnd& = AOLChild& Exit Function End If End Function Public Function FindReadWnd() As Long ' This function finds the Open Mail window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Open Mail window is found. ' If FindReadWnd() <> 0& Then MsgBox "Open Mail window found!" ' or ' If FindReadWnd() Then MsgBox "Open Mail window found!" ' This example will return the Open Mail window's handle if its found. ' If FindReadWnd() <> 0& Then MsgBox FindReadWnd() ' or ' If FindReadWnd() Then MsgBox FindReadWnd() Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, RICHCNTL As Long Dim AOLView As Long, AOLStatic As Long, AOLIcon As Long, AOLStatic2 As Long, Counter As Long Dim AOLIcon2 As Long, AOLStatic3 As Long, AOLIcon3 As Long, AOLStatic4 As Long, i As Long Dim AOLIcon4 As Long, AOLStatic5 As Long, AOLIcon5 As Long, AOLStatic6 As Long, AOLIcon6 As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) AOLStatic5& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLIcon5& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) AOLStatic6& = FindWindowEx(AOLChild&, AOLStatic5&, "_AOL_Static", vbNullString) AOLIcon6& = FindWindowEx(AOLChild&, AOLIcon5&, "_AOL_Icon", vbNullString) Do While (Counter& <> 100&) And (RICHCNTL& = 0& Or AOLView& = 0& Or AOLStatic& = 0& Or AOLIcon& = 0& Or AOLStatic2& = 0& Or AOLIcon2& = 0& Or AOLStatic3& = 0& Or AOLIcon3& = 0& Or AOLStatic4& = 0& Or AOLIcon4& = 0& Or AOLStatic5& = 0& Or AOLIcon5& = 0& Or AOLStatic6& = 0& Or AOLIcon6& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) AOLStatic& = FindWindowEx(AOLChild&, 0&, "_AOL_Static", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLStatic2& = FindWindowEx(AOLChild&, AOLStatic&, "_AOL_Static", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic3& = FindWindowEx(AOLChild&, AOLStatic2&, "_AOL_Static", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLStatic4& = FindWindowEx(AOLChild&, AOLStatic3&, "_AOL_Static", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) AOLStatic5& = FindWindowEx(AOLChild&, AOLStatic4&, "_AOL_Static", vbNullString) AOLIcon5& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) AOLStatic6& = FindWindowEx(AOLChild&, AOLStatic5&, "_AOL_Static", vbNullString) AOLIcon6& = FindWindowEx(AOLChild&, AOLIcon5&, "_AOL_Icon", vbNullString) If RICHCNTL& And AOLView& And AOLStatic& And AOLIcon& And AOLStatic2& And AOLIcon2& And AOLStatic3& And AOLIcon3& And AOLStatic4& And AOLIcon4& And AOLStatic5& And AOLIcon5& And AOLStatic6& And AOLIcon6& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindReadWnd& = AOLChild& Exit Function End If End Function Public Function FindUploadWnd() As Long ' This function finds the upload window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the upload window is found. ' If FindUploadWnd() <> 0& Then MsgBox "Upload window found!" ' or ' If FindUploadWnd() Then MsgBox "Upload window found!" ' This example will return the upload window's handle if its found. ' If FindUploadWnd() <> 0& Then MsgBox FindUploadWnd() ' or ' If FindUploadWnd() Then MsgBox FindUploadWnd() Dim AOLModal As Long, AOLStatic As Long, AOLGauge As Long Dim AOLStatic2 As Long, AOLCheckbox As Long, AOLButton As Long AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, 0&, "_AOL_Static", vbNullString) AOLGauge& = FindWindowEx(AOLModal&, 0&, "_AOL_Gauge", vbNullString) AOLGauge& = FindWindowEx(AOLModal&, AOLGauge&, "_AOL_Gauge", vbNullString) AOLStatic2& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLCheckbox& = FindWindowEx(AOLModal&, 0&, "_AOL_Checkbox", vbNullString) AOLButton& = FindWindowEx(AOLModal&, 0&, "_AOL_Button", vbNullString) AOLButton& = FindWindowEx(AOLModal&, AOLButton&, "_AOL_Button", vbNullString) Do While (Counter& <> 100&) And (AOLStatic& = 0& Or AOLGauge& = 0& Or AOLStatic2& = 0& Or AOLCheckbox& = 0& Or AOLButton& = 0&): DoEvents AOLModal& = FindWindowEx(AOLModal&, AOLModal&, "_AOL_Modal", vbNullString) AOLStatic& = FindWindowEx(AOLModal&, 0&, "_AOL_Static", vbNullString) AOLGauge& = FindWindowEx(AOLModal&, 0&, "_AOL_Gauge", vbNullString) AOLGauge& = FindWindowEx(AOLModal&, AOLGauge&, "_AOL_Gauge", vbNullString) AOLStatic2& = FindWindowEx(AOLModal&, AOLStatic&, "_AOL_Static", vbNullString) AOLCheckbox& = FindWindowEx(AOLModal&, 0&, "_AOL_Checkbox", vbNullString) AOLButton& = FindWindowEx(AOLModal&, 0&, "_AOL_Button", vbNullString) AOLButton& = FindWindowEx(AOLModal&, AOLButton&, "_AOL_Button", vbNullString) If AOLStatic& And AOLGauge& And AOLStatic2& And AOLCheckbox& And AOLButton& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindUploadWnd& = AOLModal& Exit Function End If End Function Public Function FindWelcomeWnd() As Long ' This function finds the Welcome window on AOL, and if it's found, the ' function will return the window's handle, otherwise it will return 0. This ' function is called by other subs. ' This example will bring up a message box if the Welcome window is found. ' If FindWelcomeWnd() <> 0& Then MsgBox "Welcome window found!" ' or ' If FindWelcomeWnd() Then MsgBox "Welcome window found!" ' This example will return the Welcome window's handle if its found. ' If FindWelcomeWnd() <> 0& Then MsgBox FindWelcomeWnd() ' or ' If FindWelcomeWnd() Then MsgBox FindWelcomeWnd() Dim Counter As Long, AOLIcon8 As Long, RICHCNTL7 As Long, AOLIcon7 As Long Dim RICHCNTL6 As Long, AOLIcon6 As Long, RICHCNTL5 As Long, AOLIcon5 As Long Dim RICHCNTL4 As Long, AOLIcon4 As Long, RICHCNTL3 As Long, AOLIcon3 As Long Dim RICHCNTL2 As Long, AOLIcon2 As Long, RICHCNTL As Long, i As Long Dim AOLIcon As Long, AOLChild As Long, MDIClient As Long, AOLFrame As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 5& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) RICHCNTL3& = FindWindowEx(AOLChild&, RICHCNTL2&, "RICHCNTL", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) RICHCNTL4& = FindWindowEx(AOLChild&, RICHCNTL3&, "RICHCNTL", vbNullString) AOLIcon5& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) RICHCNTL5& = FindWindowEx(AOLChild&, RICHCNTL4&, "RICHCNTL", vbNullString) AOLIcon6& = FindWindowEx(AOLChild&, AOLIcon5&, "_AOL_Icon", vbNullString) RICHCNTL6& = FindWindowEx(AOLChild&, RICHCNTL5&, "RICHCNTL", vbNullString) AOLIcon7& = FindWindowEx(AOLChild&, AOLIcon6&, "_AOL_Icon", vbNullString) RICHCNTL7& = FindWindowEx(AOLChild&, RICHCNTL6&, "RICHCNTL", vbNullString) AOLIcon8& = FindWindowEx(AOLChild&, AOLIcon7&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon8& = FindWindowEx(AOLChild&, AOLIcon8&, "_AOL_Icon", vbNullString) Next i& Do While (Counter& <> 100&) And (AOLIcon& = 0& Or RICHCNTL& = 0& Or AOLIcon2& = 0& Or RICHCNTL2& = 0& Or AOLIcon3& = 0& Or RICHCNTL3& = 0& Or AOLIcon4& = 0& Or RICHCNTL4& = 0& Or AOLIcon5& = 0& Or RICHCNTL5& = 0& Or AOLIcon6& = 0& Or RICHCNTL6& = 0& Or AOLIcon7& = 0& Or RICHCNTL7& = 0& Or AOLIcon8& = 0&): DoEvents AOLChild& = FindWindowEx(MDIClient&, AOLChild&, "AOL Child", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 5& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon2& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) Next i& RICHCNTL2& = FindWindowEx(AOLChild&, RICHCNTL&, "RICHCNTL", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon2&, "_AOL_Icon", vbNullString) AOLIcon3& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) RICHCNTL3& = FindWindowEx(AOLChild&, RICHCNTL2&, "RICHCNTL", vbNullString) AOLIcon4& = FindWindowEx(AOLChild&, AOLIcon3&, "_AOL_Icon", vbNullString) RICHCNTL4& = FindWindowEx(AOLChild&, RICHCNTL3&, "RICHCNTL", vbNullString) AOLIcon5& = FindWindowEx(AOLChild&, AOLIcon4&, "_AOL_Icon", vbNullString) RICHCNTL5& = FindWindowEx(AOLChild&, RICHCNTL4&, "RICHCNTL", vbNullString) AOLIcon6& = FindWindowEx(AOLChild&, AOLIcon5&, "_AOL_Icon", vbNullString) RICHCNTL6& = FindWindowEx(AOLChild&, RICHCNTL5&, "RICHCNTL", vbNullString) AOLIcon7& = FindWindowEx(AOLChild&, AOLIcon6&, "_AOL_Icon", vbNullString) RICHCNTL7& = FindWindowEx(AOLChild&, RICHCNTL6&, "RICHCNTL", vbNullString) AOLIcon8& = FindWindowEx(AOLChild&, AOLIcon7&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon8& = FindWindowEx(AOLChild&, AOLIcon8&, "_AOL_Icon", vbNullString) Next i& If AOLIcon& And RICHCNTL& And AOLIcon2& And RICHCNTL2& And AOLIcon3& And RICHCNTL3& And AOLIcon4& And RICHCNTL4& And AOLIcon5& And RICHCNTL5& And AOLIcon6& And RICHCNTL6& And AOLIcon7& And RICHCNTL7& And AOLIcon8& Then Exit Do Counter& = Val(Counter&) + 1& Loop If Val(Counter&) < 100& Then FindWelcomeWnd& = AOLChild& Exit Function End If End Function Public Sub ForwardFlashMail(Screennames As String, Message As String, MailIndex As Long, CloseMail As Boolean) ' This sub will forward a mail from your flashmail mailbox to whoever you ' specify. By setting CloseMail to True, the sub will close the mail about a ' half a second after clicking send, therefore making the sendmail process ' go a lot faster. ' This example will forward mail index MailIndex& from the user's flashmail mailbox. ' It will send the mail to Screennames$ with the mail message Message$ and ' the sub will close the mail. ' Screennames$ = [Screenname(s) your sending to.] ' Message$ = [Your mail message.] ' MailIndex& = [Index of mail you wish to forward.] ' Call ForwardFlashMail(Screennames$, Message$, MailIndex&, True) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim ReadWndVis As Long, ForwardWndVis As Long, AOLIcon As Long Dim AOLEdit As Long, RICHCNTL As Long, i As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) Call SendMessageByNum(AOLTree&, LB_SETCURSEL, MailIndex&, 0&) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents ReadWndVis& = IsWindowVisible(FindReadWnd()) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until ReadWndVis& = 1& Do: DoEvents AOLIcon& = FindWindowEx(FindReadWnd(), 0&, "_AOL_Icon", vbNullString) For i& = 1& To 6& AOLIcon& = FindWindowEx(FindReadWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) ForwardWndVis& = IsWindowVisible(FindForwardWnd()) Call Pause(0.1) Loop Until ForwardWndVis& = 1& AOLEdit& = FindWindowEx(FindForwardWnd(), 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screennames$) For i& = 1& To 2& AOLEdit& = FindWindowEx(FindForwardWnd(), AOLEdit&, "_AOL_Edit", vbNullString) Next i& Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Mid(GetText(AOLEdit&), 6&, Len(GetText(AOLEdit&)))) RICHCNTL& = FindWindowEx(FindForwardWnd(), 0&, "RICHCNTL", vbNullString) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) AOLIcon& = FindWindowEx(FindForwardWnd(), 0&, "_AOL_Icon", vbNullString) For i& = 1& To 11& AOLIcon& = FindWindowEx(FindForwardWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Next i& DoEvents Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) If CloseMail = True Then Call Pause(0.5) Call PostMessage(FindForwardWnd(), WM_DESTROY, 0&, 0&) Call PostMessage(FindForwardWnd(), WM_CLOSE, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindForwardWnd() = 0& Call PostMessage(FindReadWnd(), WM_CLOSE, 0&, 0&) End If End Sub Public Sub ForwardNewMail(Screennames As String, Message As String, MailIndex As Long, CloseMail As Boolean) ' This sub will forward a mail from your new mail mailbox to whoever you ' specify. By setting CloseMail to True, the sub will close the mail about a ' half a second after clicking send, therefore making the sendmail process ' go a lot faster. ' This example will forward mail index MailIndex& from the user's new mail mailbox. ' It will send the mail to Screennames$ with the mail message Message$ and ' the sub will close the mail. ' Screennames$ = [Screenname(s) your sending to.] ' Message$ = [Your mail message.] ' MailIndex& = [Index of mail you wish to forward.] ' Call ForwardNewMail(Screennames$, Message$, MailIndex&, True) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim ReadWndVis As Long, ForwardWndVis As Long, AOLIcon As Long, AOLTabPage As Long Dim AOLEdit As Long, RICHCNTL As Long, i As Long, AOLTabControl As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTree& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Tree", vbNullString) Call SendMessageByNum(AOLTree&, LB_SETCURSEL, MailIndex&, 0&) Do: DoEvents AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) ReadWndVis& = IsWindowVisible(FindReadWnd()) Call RunMenuByString("S&top Incoming Text") Call Pause(0.1) Loop Until ReadWndVis& = 1& Do: DoEvents AOLIcon& = FindWindowEx(FindReadWnd(), 0&, "_AOL_Icon", vbNullString) For i& = 1& To 6& AOLIcon& = FindWindowEx(FindReadWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) ForwardWndVis& = IsWindowVisible(FindForwardWnd()) Call Pause(0.1) Loop Until ForwardWndVis& = 1& AOLEdit& = FindWindowEx(FindForwardWnd(), 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screennames$) For i& = 1& To 2& AOLEdit& = FindWindowEx(FindForwardWnd(), AOLEdit&, "_AOL_Edit", vbNullString) Next i& Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Mid(GetText(AOLEdit&), 6&, Len(GetText(AOLEdit&)))) RICHCNTL& = FindWindowEx(FindForwardWnd(), 0&, "RICHCNTL", vbNullString) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) AOLIcon& = FindWindowEx(FindForwardWnd(), 0&, "_AOL_Icon", vbNullString) For i& = 1& To 11& AOLIcon& = FindWindowEx(FindForwardWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Next i& DoEvents Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) If CloseMail = True Then Call Pause(0.5) Call PostMessage(FindForwardWnd(), WM_DESTROY, 0&, 0&) Call PostMessage(FindForwardWnd(), WM_CLOSE, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindForwardWnd() = 0& Call PostMessage(FindReadWnd(), WM_CLOSE, 0&, 0&) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call Pause(0.3) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End If End Sub Public Function GetChatroomName() As String ' This function will return the name of the chatroom. Here's an example... ' ChatName$ = GetChatroomName() If FindChatWnd() = 0& Then Exit Sub GetChatroomName$ = GetWindowCaption(FindChatWnd()) End Function Public Function GetChatText() As String ' This function will return all of the text in the chatroom. Here's an example... ' ChatText$ = GetChatText() Dim RICHCNTL As Long RICHCNTL& = FindWindowEx(FindChatWnd(), 0&, "RICHCNTL", vbNullString) GetChatText$ = GetText(RICHCNTL&) End Function Public Function GetComboCount(hWnd As Long) As Long ' This function will return the listcount of items in a combobox. ' This example will give the number of names in the Login ' window on AOL... ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") ' Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") ' If SignOn& Then AOLChild& = SignOn&: GoTo SkipIt ' If Goodbye& Then AOLChild& = Goodbye& ' AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) ' ComboCount& = GetComboCount(AOLCombobox&) GetComboCount& = SendMessage(hWnd&, CB_GETCOUNT, 0&, 0&) End Function Public Function GetFromINI(AppName As String, KeyName As String, FileName As String) As String ' This function will return a key value from an INI file. Here's an example... ' KeyValue$ = GetFromINI("My App", "My Keyname", "myfile.ini") Dim Buffer As String Buffer$ = String(255&, Chr(0)) KeyName$ = LCase(KeyName$) GetFromINI$ = Left(Buffer$, GetPrivateProfileString(AppName$, ByVal KeyName$, "", Buffer$, Len(Buffer$), FileName$)) End Function Public Function GetInstantMessageText() As String ' This function will return the text from the instant message ' window. Here's an example... ' IMText$ = GetInstantMessageText() Dim RICHCNTL As Long If FindInstantMessageWnd() = 0& Then Exit Function RICHCNTL& = FindWindowEx(FindInstantMessageWnd(), 0&, "RICHCNTL", vbNullString) GetInstantMessageText$ = GetText(RICHCNTL&) End Function Public Function GetLastChatLine() As String ' This function will return the last message said in the chatroom. Here's an example... ' LastMsg$ = GetLastChatLine() Dim ChatText As String ChatText$ = GetChatText() GetLastChatLine$ = GetLineFromText(ChatText$, GetLineCount(ChatText$)) End Function Public Function GetLastMessageFromIM() As String ' This function will return the last message said in the IM. Here's an example... ' LastMsg$ = GetLastMessageFromIM() Dim RICHCNTL As Long, Text As String, TheirSN As String Dim txtLine As String, i As Long, LastMessage As String If FindInstantMessageWnd() = 0& Then Exit Function Text$ = GetInstantMessageText() TheirSN$ = GetScreennameFromIM() For i& = 1& To GetLineCount(Text$) txtLine$ = GetLineFromText(Text$, GetLineCount(Text$) - i& + 1&) If Mid(txtLine$, 2&, Len(TheirSN$) + 1&) = TheirSN$ & ":" Then LastMessage$ = Mid(txtLine$, Len(TheirSN$) + 5&, Len(txtLine$)) LastMessage$ = Mid(LastMessage$, 1&, Len(LastMessage$) - 1&) Exit For End If Next i& GetLastMessageFromIM$ = LastMessage$ End Function Public Function GetLineCount(Text As String) As Long ' This function will return the number of lines in the string. ' This example will get the line count from the text in Text1.Text. ' LineCount& = GetLineCount(Text1.Text) Dim CurChar As String, CurText As String Dim i As Long, LineCount As Long If Len(Text$) = 0& Then GetLineCount& = 0&: Exit Function For i& = 1 To Len(Text$) CurChar$ = Mid(Text$, i&, 1&) CurText$ = Mid(Text$, 1&, i&) If CurChar$ = Chr(13) Then LineCount& = Val(LineCount&) + 1& Next i& If Mid(Text$, Len(Text$), 1&) <> Chr(10) And Mid(Text$, Len(Text$), 1&) <> Chr(13) Then LineCount& = Val(LineCount&) + 1& GetLineCount& = LineCount& End Function Public Function GetLineFromText(Text As String, LineNumber As Long) As String ' This function will return the line, LineNumber&, from Text$. Here's an example... ' LineNumber& = [Number of line you want to extract from Text$.] ' txtLine$ = GetLineFromText(Text$, LineNumber&) Dim i As Long, LineCount As Long, strLine As String, strText As String If GetLineCount(Text$) = 0& Or LineNumber& > GetLineCount(Text$) Then Exit Function Text$ = Text$ & Chr(13) & Chr(10) For i& = 1& To Len(Text$) If Mid(Text$, i&, 1&) = Chr(13) Then LineCount& = Val(LineCount&) + 1& If LineCount& = (LineNumber& - 1&) Then If LineNumber& = 1& Then strLine$ = Mid(Text$, i&, Len(Text$)) Else strLine$ = Mid(Text$, i& + 1&, Len(Text$)) End If strLine$ = Left(strLine$, InStr(strLine$, Chr(13)) - 1&) strText$ = ReplaceText(strLine$, Chr(10), "") strText$ = ReplaceText(strLine$, Chr(13), "") GetLineFromText$ = strText$ Exit Function End If Next i& End Function Public Function GetListCount(hWnd As Long) As Long ' This function will return the number of items in a list. The following ' example will count the number of items in the flashmail mailbox. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") ' AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) ' MailCount& = GetListCount(AOLTree&) GetListCount& = SendMessage(hWnd&, LB_GETCOUNT, 0&, 0&) End Function Public Function GetMailBCC() As String ' This function will extract the Mail BCC from an open mail. Here's an example... ' MailBCC$ = GetMailBCC() Dim MailMsg As String, BCCLine As String If FindReadWnd() = 0& Then Exit Function MailMsg$ = GetText(FindReadWnd()) BCCLine$ = GetLineFromText(MailMsg$, 4&) GetMailBCC$ = Mid(BCCLine$, InStr(BCCLine$, vbTab) + 1&, Len(BCCLine$)) End Function Public Function GetMailDate() As String ' This function will extract the Mail Date from an open mail. Here's an example... ' MailDate$ = GetMailDate() Dim MailMsg As String, DateLine As String If FindReadWnd() = 0& Then Exit Function MailMsg$ = GetText(FindReadWnd()) DateLine$ = GetLineFromText(MailMsg$, 2&) GetMailDate$ = Mid(DateLine$, InStr(DateLine$, vbTab) + 1&, Len(DateLine$)) End Function Public Function GetMailSender() As String ' This function will extract the Mail Sender from an open mail. Here's an example... ' MailSender$ = GetMailSender() Dim MailMsg As String, FromLine As String If FindReadWnd() = 0& Then Exit Function MailMsg$ = GetText(FindReadWnd()) FromLine$ = GetLineFromText(MailMsg$, 3&) GetMailSender$ = Mid(FromLine$, InStr(FromLine$, vbTab) + 1&, Len(FromLine$)) End Function Public Function GetMailSubject() As String ' This function will extract the Mail Subject from an open mail. Here's an example... ' MailSubject$ = GetMailSubject() Dim MailMsg As String, SubjectLine As String If FindReadWnd() = 0& Then Exit Function MailMsg$ = GetText(FindReadWnd()) SubjectLine$ = GetLineFromText(MailMsg$, 1&) GetMailSubject$ = Mid(SubjectLine$, InStr(SubjectLine$, vbTab) + 1&, Len(SubjectLine$)) End Function Public Function GetMailTo() As String ' This function will extract the Mail To from an open mail. Here's an example... ' MailTo$ = GetMailTo() Dim MailMsg As String, ToLine As String If FindReadWnd() = 0& Then Exit Function MailMsg$ = GetText(FindReadWnd()) ToLine$ = GetLineFromText(MailMsg$, 4&) GetMailTo$ = Mid(ToLine$, InStr(ToLine$, vbTab) + 1&, Len(ToLine$)) End Function Public Sub GetMemberProfile(Screenname As String) ' This sub will get Screenname$'s profile on AOL. Here's an example... ' Screenname$ = [Screenname of the profile you want.] ' Call GetMemberProfile(Screenname$) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLEdit As Long, AOLIcon As Long Call RunPopupMenu(10&, 11&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Get a Member's Profile") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Screenname$) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Function GetRoomCount() As Long ' This function will return the number of people in the chatroom. ' This example will return how many people are in the chatroom ' through an instant message. ' MsgBox "There are " & GetRoomCount() & " people in the chatroom." AOLListbox& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) GetRoomCount& = SendMessage(AOLListbox&, LB_GETCOUNT, 0&, 0&) End Function Public Function GetScreennameFromAIMRequest() As String ' This function will return the screenname from the AIM Request ' window. Here's an example... ' Screenname$ = GetScreennameFromAIMRequest() Dim Caption As String If FindAIMAcceptWnd() = 0& Then Exit Function Caption$ = GetWindowCaption(FindAIMAcceptWnd()) GetScreennameFromAIMRequest$ = Mid(Caption$, InStr(Caption$, ": ") + 2, Len(Caption$)) End Function Public Function GetScreennameFromIM() As String ' This function will return the screenname from the Instant ' Message window. Here's an example... ' Screenname$ = GetScreennameFromIM() Dim Caption As String If FindInstantMessageWnd() = 0& Then Exit Function Caption$ = GetWindowCaption(FindInstantMessageWnd()) GetScreennameFromIM$ = Mid(Caption$, InStr(Caption$, ": ") + 2, Len(Caption$)) End Function Public Function GetStockQuote(StockSymbol As String) As String ' This function will return stock information on the stock symbol ' in StockSymbol$. Here's an example... ' StockQuote$ = GetStockQuote("MSFT") Dim AOLFrame As Long, AOLToolbar As Long, AOLToolbar2 As Long, Counter As Long Dim AOLIcon As Long, MDIClient As Long, AOLChild As Long, i As Long Dim AOLEdit As Long, AOLView As Long, Quote As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLToolbar& = FindWindowEx(AOLFrame&, 0&, "AOL Toolbar", vbNullString) AOLToolbar2& = FindWindowEx(AOLToolbar&, 0&, "_AOL_Toolbar", vbNullString) AOLIcon& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 10& AOLIcon& = FindWindowEx(AOLToolbar2&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call ClickIcon(AOLIcon&) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "AOL Investment Snapshot") AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) AOLView& = FindWindowEx(AOLChild&, 0&, "_AOL_View", vbNullString) AOLView& = FindWindowEx(AOLChild&, AOLView&, "_AOL_View", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLEdit& And AOLView& Call SetText(AOLEdit&, StockSymbol$) Call Pause(0.1) Call SendMessageLong(AOLEdit&, WM_CHAR, 13&, 0&) Call WaitForTextToLoad(AOLView&) Quote$ = GetText(AOLView&) Call CloseWindow(AOLChild&) GetStockQuote$ = Quote$ End Function Public Function GetText(hWnd As Long) As String ' This function will return the text from a hWnd. The following ' example will return the text from the chatroom. ' RICHCNTL& = FindWindowEx(FindChatWnd(), 0&, "RICHCNTL", vbNullString) ' ChatText$ = GetText(RICHCNTL&) Dim TextLen As Long, hWndTxt As String TextLen& = SendMessage(hWnd&, WM_GETTEXTLENGTH, 0&, 0&) hWndTxt$ = String(TextLen&, 0&) Call SendMessageByString(hWnd&, WM_GETTEXT, TextLen& + 1&, hWndTxt$) GetText$ = hWndTxt$ End Function Public Function GetWindowCaption(hWnd As Long) As String ' This function will return the caption of a window. The following ' example will return the name of the chatroom. ' ChatName$ = GetWindowCaption(FindChatWnd()) Dim CaptionLen As Long, WndCaption As String CaptionLen& = SendMessage(hWnd&, WM_GETTEXTLENGTH, 0&, 0&) WndCaption$ = String(CaptionLen&, 0&) Call SendMessageByString(hWnd&, WM_GETTEXT, CaptionLen& + 1&, WndCaption$) GetWindowCaption$ = WndCaption$ End Function Public Sub HideWindow(hWnd As Long) ' This sub will hide a window. The following example will ' hide AOL. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call HideWindow(AOLFrame&) Call ShowWindow(hWnd&, SW_HIDE) End Sub Public Sub HoverButton(Frm As Form, MouseAway As PictureBox, MouseOver As PictureBox, BorderStyle As FormBorderStyleConstants) ' The following sub will automatically hide/show buttons on ' your form, acting as "Hover Buttons". You would put this ' sub in a timer with an interval of 1 to 100. ' Note: BorderStyle must contain a valid Form Border Style ' Constant, depending on the border style of the form your ' buttons are on. ' In the following example, Picture1 acts as the main button, ' but then when the mouse is moved over Picture1, Picture2 ' would then be visible. Keep in mind that Picture2's Visible ' property is set to False. Then you put your coding (whatever ' you want to happen when the button is clicked) in Picture2's ' "Click" event. Form1 is used because that is the form that ' the buttons are on. In this example, I used "vbBSNone" ' because Form1 has no border style, and "vbBSNone" is ' the constant for no border. ' Call HoverButton(Form1, Picture1, Picture2, vbBSNone) Dim ptCursor As POINTAPI Call GetCursorPos(ptCursor) Select Case BorderStyle Case vbBSNone: If (ptCursor.X > (Frm.Left + MouseAway.Left) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If Case vbFixedDialog: If (ptCursor.X > (Frm.Left + MouseAway.Left + 30&) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width + 45&) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top + 315&) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height + 330&) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If Case vbFixedSingle: If (ptCursor.X > (Frm.Left + MouseAway.Left + 30&) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width + 45&) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top + 315&) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height + 330&) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If Case vbFixedToolWindow: If (ptCursor.X > (Frm.Left + MouseAway.Left + 30&) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width + 45&) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top + 225&) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height + 240&) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If Case vbSizable: If (ptCursor.X > (Frm.Left + MouseAway.Left + 45&) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width + 60&) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top + 330&) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height + 345&) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If Case vbSizableToolWindow: If (ptCursor.X > (Frm.Left + MouseAway.Left + 45&) / Screen.TwipsPerPixelX) And (ptCursor.X < (Frm.Left + MouseAway.Left + MouseAway.Width + 60&) / Screen.TwipsPerPixelX) And (ptCursor.Y > (Frm.Top + MouseAway.Top + 240&) / Screen.TwipsPerPixelX) And (ptCursor.Y < (Frm.Top + MouseAway.Top + MouseAway.Height + 255&) / Screen.TwipsPerPixelX) Then MouseOver.Top = MouseAway.Top MouseOver.Left = MouseAway.Left MouseOver.Visible = True Else MouseOver.Visible = False End If End Select End Sub Public Sub IgnoreScreenname(Screenname As String) ' This sub will ignore instant messages from the screenname ' you specify in Screenname$. Here's an example... ' Screenname$ = [The screenname you want to ignore IM's from.] ' Call IgnoreScreenname(Screenname$) Call SendInstantMessage("$im_off " & Screenname$, " ", True) End Sub Public Function IsItemInCombobox(hWnd As Long, SearchString As String) As Boolean ' This function will search in a combobox (hWnd&) for the search ' string (SearchString$), and if the item is found, the function will ' return False, but if the item is not found, the function will return False. ' Here's an example using this function... ' Note: This function searches in the login screennames combo box. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") ' Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") ' If SignOn& Then AOLChild& = SignOn&: GoTo SkipIt ' If Goodbye& Then AOLChild& = Goodbye& ' SkipIt: ' AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) ' SearchString$ = [String you want to search for.] ' If IsItemInCombobox(AOLCombobox&, SearchString$) Then ' MsgBox "The search string was found." ' Else ' MsgBox "The search string was not found." ' End If Dim hProcess As Long, Index As Long, Item As String, lpNumberOfBytesWritten As Long Dim ItemData As Long, Dest As Long, lpdwProcessId As Long On Error Resume Next Call GetWindowThreadProcessId(hWnd&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(hWnd&, CB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(hWnd&, CB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) If InStr(Trim(LCase(Item$)), Trim(LCase(SearchString$))) Then IsItemInCombobox = True: Exit For Next Index& Call CloseHandle(hProcess&) End Function Public Function IsItemInListbox(hWnd As Long, SearchString As String) As Boolean ' This function will search in a listbox (hWnd&) for the search ' string (SearchString$), and if the item is found, the function will ' return False, but if the item is not found, the function will return False. ' Here's an example using this function... ' Note: This function searches in the screennames listbox in the chatroom. ' AOLListbox& = FindWindowEx(FindChatWnd(), 0&, "_AOL_Listbox", vbNullString) ' SearchString$ = [String you want to search for.] ' If IsItemInTree(AOLListbox&, SearchString$) Then ' MsgBox "The search string was found." ' Else ' MsgBox "The search string was not found." ' End If Dim hProcess As Long, Index As Long, Item As String, lpNumberOfBytesWritten As Long Dim ItemData As Long, Dest As Long, lpdwProcessId As Long On Error Resume Next Call GetWindowThreadProcessId(hWnd&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(hWnd&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(hWnd&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Trim(Left(Item$, InStr(Item$, vbNullChar) - 1&)) If InStr(Trim(LCase(Item$)), Trim(LCase(SearchString$))) Then IsItemInListbox = True: Exit For Next Index& Call CloseHandle(hProcess&) End Function Public Function IsItemInTree(hWnd As Long, SearchString As String) As Boolean ' This function will search in a tree (hWnd&) for the search ' string (SearchString$), and if the item is found, the function will ' return False, but if the item is not found, the function will return False. ' Here's an example using this function... ' Note: This function searches in the login screennames combo box. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) ' AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") ' AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) ' SearchString$ = [String you want to search for.] ' If IsItemInTree(AOLTree&, SearchString$) Then ' MsgBox "The search string was found." ' Else ' MsgBox "The search string was not found." ' End If Dim i As Long, TxtLength As Long, TreeTxt As String For i& = 0& To GetListCount(hWnd&) - 1& TxtLength& = SendMessage(hWnd&, LB_GETTEXTLEN, i&, 0&) TreeTxt$ = String(TxtLength& + 1&, 0&) Call SendMessageByString(hWnd&, LB_GETTEXT, i&, TreeTxt$) If InStr(Trim(LCase(TreeTxt$)), Trim(LCase(SearchString$))) Then IsItemInTree = True: Exit For Next i& End Function Public Function IsSignedOn() As Boolean ' This function finds out if the user is signed on. Here's an example: ' If IsSignedOn() = 0 Then MsgBox "Not Signed On!" If FindWelcomeWnd() <> 0& Then IsSignedOn = True Else IsSignedOn = False End If End Function Public Function IsValidScreenname(Screenname As String) As Boolean ' This function will check to see if a screenname is valid ' or not. It will return True if the screenname is valid and ' False if the screenname is invalid. Here's an example... ' Screenname$ = [Screenname you want to check.] ' If IsValidScreenname(Screenname$) Then ' Screenname is valid. ' Else ' Screenname is invalid. ' End If Dim TmpScreenname As String If Len(Screenname$) < 3& Or Len(Screenname$) > 16& Then IsValidScreenname = False: Exit Function TmpScreenname$ = ReplaceText(Screenname$, " ", "") If Len(TmpScreenname$) < 3& Then IsValidScreenname = False: Exit Function IsValidScreenname = True End Function Public Sub KeepFormOnBottom(Frm As Form) ' This sub will keep your form on bottom of all other's and other applications. ' This example will keep the current from on bottom. ' Call KeepFromOnBottom(Me) Call SetWindowPos(Frm.hWnd, HWND_NOTOPMOST, 0&, 0&, 0&, 0&, FLAGS) End Sub Public Sub KeepFormOnTop(Frm As Form) ' This sub will keep your form ontop of all other's and other applications. ' This example will keep the current from on top. ' Call KeepFromOnTop(Me) Call SetWindowPos(Frm.hWnd, HWND_TOPMOST, 0&, 0&, 0&, 0&, FLAGS) End Sub Public Sub Keyword(Address As String) ' This sub will run an AOL Keyword. Here's an example... ' Call Keyword("http://www.bofen.com") Dim AOLFrame As Long, AOLToolbar As Long, AOLToolbar2 As Long Dim AOLCombobox As Long, Edit As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLToolbar& = FindWindowEx(AOLFrame&, 0&, "AOL Toolbar", vbNullString) AOLToolbar2& = FindWindowEx(AOLToolbar&, 0&, "_AOL_Toolbar", vbNullString) AOLCombobox& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Combobox", vbNullString) Edit& = FindWindowEx(AOLCombobox&, 0&, "Edit", vbNullString) Call SendMessageByString(Edit&, WM_SETTEXT, 0&, Address$) Call SendMessageLong(Edit&, WM_CHAR, VK_SPACE, 0&) Call SendMessageLong(Edit&, WM_CHAR, VK_RETURN, 0&) End Sub Public Sub KillWait() ' This sub will kill the hour glass. Here's an example... ' Call KillWait Dim AOLModal As Long, AOLModVis As Long, AOLIcon As Long Call RunMenuByString("&About America Online") Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub LoadListFile(FilePath As String, Ctrl As Control, SkipBlankLines As Boolean) ' This sub will add all the lines from a text file into a control. ' Like how a pwc loads screennames to a list from a text ' file. You can also have the sub skip blank lines. ' This example will load sn.txt into a list and will skip blank ' lines. ' MyFiles$ = "C:\MyFolder\MyFile.txt" ' Call LoadListFile(MyFile$, List1, True) Dim strLine As String Open FilePath$ For Input As #1 Do If EOF(1) Then Exit Do Line Input #1, strLine$ If Len(strLine$) = 0& Then If SkipBlankLines = False Then Ctrl.AddItem strLine$ Else Ctrl.AddItem strLine$ End If Loop Close #1 End Sub Public Function LoadTextFile(FilePath As String) As String ' This function will load a text file. The following example ' will put all the text from MyFile$ into the string Text$. ' MyFile$ = "C:\MyFolder\MyFile.txt" ' Text$ = LoadTextFile(MyFile$) Dim Text As String Open FilePath$ For Input As 1& Let Text$ = Input$(LOF(1&), 1&) Close 1& LoadTextFile$ = Text$ End Function Public Sub MaximizeWindow(hWnd As Long) ' This sub will maximize a window. The following example ' will maximize AOL. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call MaximizeWindow(AOLFrame&) Call ShowWindow(hWnd&, SW_MAXIMIZE) End Sub Public Sub MinimizeWindow(hWnd As Long) ' This sub will minimize a window. The following example ' will minimize AOL. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call MinimizeWindow(AOLFrame&) Call ShowWindow(hWnd&, SW_MINIMIZE) End Sub Public Sub NormalizeWindow(hWnd As Long) ' This sub will normalize a window. The following example ' will normalize AOL. ' Note: By normalize, I mean put the window to its original ' window state. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call NormalizeWindow(AOLFrame&) Call ShowWindow(hWnd&, SW_NORMAL) End Sub Public Sub OpenFlashMail() ' This sub will open your flashmail mailbox and wait for the mail to load. ' Here's an example on how to call this sub: ' Call OpenFlashMail Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim ListCount1 As Long, ListCount2 As Long, ListCount3 As Long Call RunPopupMenu(3&, 12&, True, 1&) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Incoming/Saved Mail") AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLTree& AOLTree& = FindWindowEx(AOLChild&, 0&, "_AOL_Tree", vbNullString) Do: DoEvents ListCount1& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount2& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount3& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Loop Until ListCount2& = ListCount1& And ListCount3& = ListCount1& End Sub Public Sub OpenNewMail() ' This sub will open your new mail mailbox and wait for the mail to load. ' Here's an example on how to call this sub: ' Call OpenNewMail Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLTree As Long Dim AOLTabControl As Long, AOLTabPage As Long Dim ListCount1 As Long, ListCount2 As Long, ListCount3 As Long Call RunPopupMenu(3&, 2&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Online Mailbox") AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTree& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Tree", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLTabControl& And AOLTabPage& And AOLTree& AOLTabControl& = FindWindowEx(AOLChild&, 0&, "_AOL_TabControl", vbNullString) AOLTabPage& = FindWindowEx(AOLTabControl&, 0&, "_AOL_TabPage", vbNullString) AOLTree& = FindWindowEx(AOLTabPage&, 0&, "_AOL_Tree", vbNullString) Do: DoEvents ListCount1& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount2& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount3& = SendMessage(AOLTree&, LB_GETCOUNT, 0&, 0&) Loop Until ListCount2& = ListCount1& And ListCount3& = ListCount1& End Sub Public Sub Pause(Interval) ' This sub will pause for the inputed amount of time (in seconds). Here is an example: ' This example will hault your program for 1 second. ' Call Pause(1) Dim CurrentTime As Long CurrentTime& = Timer Do While Timer - CurrentTime& < Val(Interval): DoEvents Loop End Sub Public Sub RemoveBuddyFromBuddyList(Buddies As String, GroupName As String) ' This sub will remove buddy(s) from one of the user's buddy groups. ' This example will remove "Screenname" from the buddy group named "My Buddies". ' Call RemoveBuddyFromBuddyList("Screenname", "My Buddies") ' This example will remove 3 buddies from the buddy group named "My Buddies". ' Buddies$ = "Screenname 1" & Chr(13) & Chr(10) & "Screenname 2" & Chr(13) & Chr(10) & "Screenname 3" ' Call RemoveBuddyFromBuddyList(Buddies$, "My Buddies") Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, UpdateMsg As Long, Changes As Boolean Dim AOLIcon As Long, i As Long, BuddyLists As Long, BuddyListsVis As Long, Button As Long Dim hProcess As Long, Index As Long, Item As String, ItemData As Long, Dest As Long Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long, AOLEdit As Long, FoundScreenname As Boolean Dim Screenname As String, AOLListbox As Long, AOLStatic As Long, UpdateMsgVis As Long On Error Resume Next If Len(Trim(Buddies$)) < 3 Then Exit Sub AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) If FindEditBuddyWnd() = 0& Then AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call Pause(0.1) Loop Until AOLChild& And AOLIcon& And AOLListbox& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& AOLListbox& = FindWindowEx(BuddyLists&, 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(AOLListbox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLListbox&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLListbox&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Left(Item$, InStr(Item$, vbNullChar) - 1&) If Trim(LCase(Mid(Item$, 1&, Len(GroupName$)))) = LCase(Trim(GroupName$)) Then Call SelectItemFromListbox(AOLListbox&, Index&): Exit For Next Index& Call CloseHandle(hProcess&) AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(BuddyLists&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents Call Pause(0.1) Loop Until FindEditBuddyWnd() End If For i& = 1& To GetLineCount(Buddies$) Screenname$ = GetLineFromText(Buddies$, i&) If IsValidScreenname(Screenname$) Then AOLListbox& = FindWindowEx(FindEditBuddyWnd(), 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(AOLListbox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLListbox&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLListbox&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Left(Item$, InStr(Item$, vbNullChar) - 1&) FoundScreenname = False If Trim(LCase(Mid(Item$, 1&, Len(Screenname$)))) = LCase(Trim(Screenname$)) Then FoundScreenname = True: Changes = True: Call SelectItemFromListbox(AOLListbox&, Index&): Exit For Next Index& Call CloseHandle(hProcess&) AOLIcon& = FindWindowEx(FindEditBuddyWnd(), 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(FindEditBuddyWnd(), AOLIcon&, "_AOL_Icon", vbNullString) If FoundScreenname = True Then Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) AOLEdit& = FindWindowEx(FindEditBuddyWnd(), 0&, "_AOL_Edit", vbNullString) AOLEdit& = FindWindowEx(FindEditBuddyWnd(), AOLEdit&, "_AOL_Edit", vbNullString) Do: DoEvents Call Pause(0.1) Loop Until LCase(Trim(GetText(AOLEdit&))) = LCase(Trim(Screenname$)) End If End If Next i& AOLIcon& = FindWindowEx(FindEditBuddyWnd(), AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) If Changes = True Then Do: DoEvents UpdateMsg& = FindWindow("#32770", "America Online") UpdateMsgVis& = IsWindowVisible(UpdateMsg&) Call Pause(0.1) Loop Until UpdateMsgVis& = 1& Button& = FindWindowEx(UpdateMsg&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents UpdateMsg& = FindWindow("#32770", "America Online") Call Pause(0.1) Loop Until UpdateMsg& = 0& End If Do: DoEvents Call Pause(0.1) Loop Until FindEditBuddyWnd() = 0& BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call CloseWindow(BuddyLists&) End Sub Public Sub RenameFile(OldFilePath As String, NewFilePath As String) ' This sub will rename a file. The following example will ' rename "C:\MyFolder\MyFile.txt" to "C:\MyNewFile.txt". ' Call RenameFile("C:\MyFolder\MyFile.txt", "C:\MyNewFile.txt") Name OldFilePath$ As NewFilePath$ End Sub Public Function ReplaceText(Text As String, Find As String, Replace As String) As String ' This sub will replace the Find string with Replace string in Text. Here is an example: ' This example replaces "Hello" with "Goodbye" in MyString$. ' MyString$ = "Hello world!" ' MyString$ = ReplaceText(MyString$, "Hello", "Goodbye") ' MyString$ would now be "Goodbye World!" Dim strLeft As String, strRight As String, strNew As String Dim strIns As Long strIns& = InStr(Text$, Find$) If strIns& = 0 Then ReplaceText$ = Text$ Exit Function End If Do: DoEvents strLeft$ = Left(Text$, strIns - 1) strRight$ = Mid(Text$, strIns + Len(Find$)) strNew$ = strLeft$ & Replace$ & strRight$ Text$ = strNew$ strIns& = InStr(Text$, Find$) Loop Until strIns& = 0& ReplaceText$ = Text$ End Function Public Sub RunFlashSession(SignOffWhenFinished As Boolean) ' This sub will run a flash session, and you can have the ' sub sign off AOL when the flash session is completed ' by setting SignOffWhenFinished to True. ' This example will run a flash session and will not sign ' off AOL after session is completed. ' Call RunFlashSession(False) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLCheckbox As Long, AOLIcon As Long Dim AOLModal As Long, AOLModVis As Long Call RunPopupMenu(3&, 10&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Automatic AOL") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, True, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) DoEvents Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", vbNullString) AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLCheckbox& = FindWindowEx(AOLModal&, 0&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, SignOffWhenFinished, 0&) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) DoEvents Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub RunMenu(X As Long, Y As Long) ' This sub will run an AOL menu. The following example ' will run 'About America Online' from the help menu. ' Note: X and Y coordinates start at 0, not 1. ' Call RunMenu(4&, 7&) Dim AOLFrame As Long, AOLMenu As Long Dim AOLSubMenu As Long, AOLMenuID As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLMenu& = GetMenu(AOLFrame&) AOLSubMenu& = GetSubMenu(AOLMenu&, X&) AOLMenuID& = GetMenuItemID(AOLSubMenu&, Y&) Call SendMessageLong(AOLFrame&, WM_COMMAND, AOLMenuID&, 0&) End Sub Public Sub RunMenuByString(strString As String) ' This sub will run an AOL menu by string. The following ' example will run 'Stop Incoming Text' from the 'File' menu. ' Note: Remember that if a character is underlined in the ' menu, that you must put a "&" in front of it, you'll see ' what I mean in the following example. ' Call RunMenuByString("S&top Incoming Text") Dim AOLFrame As Long, AOLMenu As Long Dim AOLSubMenu As Long, AOLMenuID As Long Dim X As Long, Y As Long Dim lpString As String AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLMenu& = GetMenu(AOLFrame&) For X& = 0& To GetMenuItemCount(AOLMenu&) - 1& AOLSubMenu& = GetSubMenu(AOLMenu&, X&) For Y& = 0& To GetMenuItemCount(AOLSubMenu&) - 1& AOLMenuID& = GetMenuItemID(AOLSubMenu&, Y&) lpString$ = String(100&, " ") Call GetMenuString(AOLSubMenu&, AOLMenuID&, lpString$, 100&, 1&) If InStr(LCase(lpString$), LCase(strString$)) Then Call SendMessageLong(AOLFrame&, WM_COMMAND, AOLMenuID&, 0&): Exit Sub Next Y& Next X& End Sub Public Sub RunPopupMenu(X As Long, Y As Long, SubMenu As Boolean, Optional Z As Long) ' This sub will run AOL's popup menus. Here are some examples: ' This example will run "Mail Center" from the Mail Center menu. ' Call RunPopupMenu(3&, 1&, False) ' This example will run "Incoming/Saved Mail" from the Mail Center menu. ' Call RunPopupMenu(3&, 12&, True, 1&) ' This example will run "Edit Shortcuts" from the Favorites menu. ' Call RunPopupMenu(7&, 4&, True, 1&) ' This example will run "Download Manager" from the My Files menu. ' Call RunPopupMenu(5&, 4&, False) ' This example will run "Copies of Mail You've Sent" from the Mail Center menu. ' Call RunPopupMenu(3&, 12&, True, 3&) Dim AOLFrame As Long, TextLen As Long, AOLIcon As Long, AOLToolbar As Long Dim AOLToolbar2 As Long, PopMenu As Long, PopMenuVis As Long, i As Long Dim AOLFrameTxt As String Dim CursorPos As POINTAPI Call GetCursorPos(CursorPos) Call SetCursorPos(Screen.Width, Screen.Height) AOLFrame& = FindWindow("AOL Frame25", vbNullString) TextLen& = SendMessage(AOLFrame&, WM_GETTEXTLENGTH, 0&, 0&) AOLFrameTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLFrame&, WM_GETTEXT, TextLen& + 1&, AOLFrameTxt$) AppActivate AOLFrameTxt$ AOLToolbar& = FindWindowEx(AOLFrame&, 0&, "AOL Toolbar", vbNullString) AOLToolbar2& = FindWindowEx(AOLToolbar&, 0&, "_AOL_Toolbar", vbNullString) If X& = 1& Then AOLIcon& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Icon", vbNullString) Else AOLIcon& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Icon", vbNullString) For i& = 1 To X& - 1& AOLIcon& = FindWindowEx(AOLToolbar2&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& End If Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents PopMenu& = FindWindow("#32768", vbNullString) PopMenuVis& = IsWindowVisible(PopMenu&) Loop Until PopMenuVis& = 1& For i& = 1& To Y& Call PostMessage(PopMenu&, WM_KEYDOWN, VK_DOWN, 0&) Call PostMessage(PopMenu&, WM_KEYUP, VK_DOWN, 0&) Next i& If SubMenu = True Then Call PostMessage(PopMenu&, WM_KEYDOWN, VK_RIGHT, 0&) Call PostMessage(PopMenu&, WM_KEYUP, VK_RIGHT, 0&) For i& = 1& To Z& - 1& Call PostMessage(PopMenu&, WM_KEYDOWN, VK_DOWN, 0&) Call PostMessage(PopMenu&, WM_KEYUP, VK_DOWN, 0&) Next i& End If Call PostMessage(PopMenu&, WM_KEYDOWN, VK_RETURN, 0&) Call PostMessage(PopMenu&, WM_KEYUP, VK_RETURN, 0&) Call SetCursorPos(CursorPos.X, CursorPos.Y) End Sub Public Sub RespondToIM(Message As String) ' This sub will respond to the top IM Window, and ' will close it once responded. This is good for an ' Auto-IM Responder, so you would put the following ' example into a timer with an interval of 100 or ' whatever you want. ' Message$ = [What you want to say.] ' Call RespondToIM(Message$) Dim TheirSN As String If FindInstantMessageWnd() = 0& Then Exit Sub TheirSN$ = GetScreennameFromIM() Call CloseWindow(FindInstantMessageWnd()) Call SendInstantMessage(TheirSN$, Message$, True) End Sub Public Sub RunAOLShortCut(ShortCutNum As Long) ' This sub will run an AOL shortcut from the Shortcut ' menu. Here's an example... ' Note: There are only 10 shortcuts on AOL. ' Call RunShortCut(1&) Call RunPopupMenu(7&, 4&, True, ShortCutNum& + 1&) End Sub Public Sub SaveTextFile(FilePath As String, Text As String) ' This sub will save text to a file. The following example ' will save Text$ to "C:\MyFolder\MyFile.txt". ' Text$ = [The text you want to save.] ' Call SaveTextFile("C:\MyFolder\MyFile.txt", Text$) Open FilePath$ For Output As #1 Print #1, Text$ Close #1 End Sub Public Function ScanFileForString(FilePath As String, SearchString As String) As Boolean ' This sub will search a file for a string. Like how a pwsd or ' virus scanner scan files. The funciton will return True if the ' search string is found, and will return False if the string is not ' found. Here's an example... ' If ScanFileForString(FilePath$, SearchString$) Then ' String was found in file. ' Else ' String was not found in file. ' End if Dim Buffer As String On Error Resume Next Open FilePath$ For Binary Access Read Write As #1 Buffer$ = String(LOF(1), " ") Get #1, 1, Buffer$ If InStr(LCase(Buffer$), LCase(SearchString$)) Then ScanFileForString = True Close #1 End Function Public Function ScreennameAvailable(Screenname As String) As Boolean ' This function will return True if Screenname$ is online and able to recieve ' instant messages, and it will return False if Screenname$ is signed off or ' has their IM's turned off. Here's an example: ' This example will bring up a messagebox stating Screenname's availability. ' If ScreennameAvailable("Screenname") = True Then ' MsgBox "Screenname is online and can recieve instant messages." ' Else ' MsgBox "Screenname is either signed off or has their IM's turned off." ' End If Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLEdit As Long, RICHCNTL As Long, AOLIcon As Long, i As Long Dim AOLStatic As Long, MsgWnd As Long, Button As Long, TextLen As Long Dim AOLStaticTxt As String, Available As Boolean Call RunPopupMenu(10&, 6&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Send Instant Message") Call Pause(0.1) Loop Until AOLChild& AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Send Instant Message") AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screenname$) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 9& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.01) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgWnd& = FindWindow("#32770", "America Online") Call Pause(0.1) Loop Until MsgWnd& MsgWnd& = FindWindow("#32770", "America Online") AOLStatic& = FindWindowEx(MsgWnd&, 0&, "Static", vbNullString) AOLStatic& = FindWindowEx(MsgWnd&, AOLStatic&, "Static", vbNullString) TextLen& = SendMessage(AOLStatic&, WM_GETTEXTLENGTH, 0&, 0&) AOLStaticTxt$ = String(TextLen&, 0&) Call SendMessageByString(AOLStatic&, WM_GETTEXT, TextLen& + 1&, AOLStaticTxt$) If InStr(AOLStaticTxt$, " is not currently signed on.") Or InStr(AOLStaticTxt$, " cannot currently receive Instant Messages.") Then Available = False Else Available = True End If Button& = FindWindowEx(MsgWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Call PostMessage(AOLChild&, WM_CLOSE, 0&, 0&) ScreennameAvailable = Available End Function Public Sub ScrollMacro(Macro As String) ' This sub will scroll a macro to the chatroom. The ' following example will scroll Macro$ to the chatroom, ' so imagine that the macro is stored in Macro$. ' Call ScrollMacro(Macro$) Dim i As Long, txtLine As String For i& = 1& To GetLineCount(Macro$): DoEvents If InStr(Val(i& / 4&), ".") = False Then Call Pause(2) txtLine$ = GetLineFromText(Macro$, i&) If Len(txtLine$) <> 0& Then Call SendToChat(txtLine$) Else Call SendToChat(" ") End If Next i& End Sub Public Sub SearchAOL(SearchString As String) ' This sub will run a search for SearchString$ on AOL's ' new search engine. Here's an example... ' SearchString$ = [String to search for.] ' Call SearchAOL(SearchString$) Call Keyword("http://aolsearch.aol.com/dirsearch.adp?query=" & LCase(SearchString$)) End Sub Public Sub SearchMemberDirectory(SearchString As String, Optional MemberName As String, Optional Location As String) ' This sub will search AOL's member directory. Here's an example... ' Note: MemberName and Location are optional. ' SearchString$ = [String to search for.] ' MemberName$ = [Member name to search for.] ' Location$ = [Location to search for.] ' Call SearchMemberDirectory(SearchString$, MemberName$, Location$) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLChildVis As Long, AOLEdit As Long, AOLIcon As Long Call RunPopupMenu(10&, 9&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Member Directory") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, SearchString$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) If Len(MemberName$) <> 0& Then Call SetText(AOLEdit&, MemberName$) AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) If Len(Location$) <> 0& Then Call SetText(AOLEdit&, Location$) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub SelectItemFromCombobox(hWnd As Long, Index As Long) ' This sub will select an item from a combo box by index. ' Here's an example... ' hWnd& = [Combobox handle.] ' Index& = [Index number of item to select.] ' Call SelectItemFromCombobox(hWnd&, Index&) Call SendMessage(hWnd&, CB_SETCURSEL, Index&, 0&) End Sub Public Sub SelectItemFromListbox(hWnd As Long, Index As Long) ' This sub will select an item from a list box (or tree) by index. ' Here's an example... ' hWnd& = [Combobox handle.] ' Index& = [Index number of item to select.] ' Call SelectItemFromListbox(hWnd&, Index&) Call SendMessage(hWnd&, LB_SETCURSEL, Index&, 0&) End Sub Public Sub SelectLoginScreenname(TheScreenname As String) ' This sub will select TheScreenname$ from the Sign On ' window's screenname combo box. Here's an example... ' Screenname$ = [Screenname to select.] ' Call SelectLoginScreenname(Screenname$) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim SignOn As Long, Goodbye As Long, AOLCombobox As Long Dim RoomList As Long, hProcess As Long, Index As Long, SpaceCount As Long Dim ItemData As Long, Dest As Long, i As Long, Screenname As String Dim lpdwProcessId As Long, lpNumberOfBytesWritten As Long On Error Resume Next AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") If SignOn& Then AOLChild& = SignOn&: GoTo SkipIt If Goodbye& Then AOLChild& = Goodbye& SkipIt: If AOLChild& = 0& Then Exit Sub AOLCombobox& = FindWindowEx(AOLChild&, 0&, "_AOL_Combobox", vbNullString) Call GetWindowThreadProcessId(AOLCombobox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLCombobox&, CB_GETCOUNT, 0&, 0&) - 1& Screenname$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLCombobox&, CB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Screenname$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Screenname$, 4&) Dest& = Dest& + 6& Screenname$ = String(16&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Screenname$, 16&, lpNumberOfBytesWritten&) Screenname$ = Trim(Screenname$) If LCase(Trim(Screenname$)) = LCase(Trim(TheScreenname$)) Then Call SendMessage(AOLCombobox&, CB_SETCURSEL, Index&, 0&) Next Index& Call CloseHandle(hProcess&) End Sub Public Sub SendInstantMessage(Screenname As String, Message As String, CloseIM As Boolean) ' This sub will send an instant message to Screenname$ with Message$ as the message. ' This example will send an instant message to SN$ and will close the IM window. ' SN$ = "Screenname" ' Msg$ = "What's up " & SN$ & "?" ' Call InstantMessage(SN$, Msg$, True) ' This example will send an instant message to SN$ and will NOT close the IM window. ' SN$ = "Screenname" ' Msg$ = "What's up " & SN$ & "?" ' Call InstantMessage(SN$, Msg$, False) ' This example will turn your IM's off. ' Call InstantMessage("$im_off", " ", True) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long Dim AOLEdit As Long, RICHCNTL As Long, AOLIcon As Long, i As Long Dim OpenIM As Long, MsgWnd As Long, Button As Long Call RunPopupMenu(10&, 6&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Send Instant Message") AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 8& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Loop Until AOLChild& And AOLEdit& And RICHCNTL& And AOLIcon& Call Pause(0.1) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screenname$) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents OpenIM& = FindWindowEx(MDIClient, 0&, "AOL Child", " Instant Message To: " & Screenname$) MsgWnd& = FindWindow("#32770", "America Online") Call Pause(0.1) Loop Until OpenIM& Or MsgWnd& If OpenIM& Then If CloseIM = True Then OpenIM& = FindWindowEx(MDIClient, 0&, "AOL Child", " Instant Message To: " & Screenname$) Call PostMessage(OpenIM&, WM_CLOSE, 0&, 0&) End If Else OpenIM& = FindWindowEx(MDIClient, 0&, "AOL Child", " Instant Message To: " & Screenname$) MsgWnd& = FindWindow("#32770", "America Online") Button& = FindWindowEx(MsgWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Call PostMessage(AOLChild&, WM_CLOSE, 0&, 0&) End If End Sub Public Sub SendMail(Screenname As String, Subject As String, Message As String) ' This sub will send mail to Screenname$ with the subject Subject$ and the message ' Message$. Here's an example: ' Call SendMail("Screenname", "Whats up? Read this...", "My super cool message here.") Dim AOLFrame As Long, AOLToolbar As Long, AOLToolbar2 As Long Dim AOLIcon As Long, MDIClient As Long, AOLChild As Long Dim AOLEdit As Long, RICHCNTL As Long, i As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLToolbar& = FindWindowEx(AOLFrame&, 0&, "AOL Toolbar", vbNullString) AOLToolbar2& = FindWindowEx(AOLToolbar&, 0&, "_AOL_Toolbar", vbNullString) AOLIcon& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLToolbar2&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Write Mail") AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) For i& = 1& To 2& AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Next i& RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 13& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Loop Until AOLChild& And AOLEdit& And RICHCNTL& And AOLIcon& Call Pause(0.1) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screenname$) For i& = 1& To 2& AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Next i& Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Subject$) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub SendMailWithAttachments(Screenname As String, Subject As String, Message As String, FileCount As Long, Files()) ' This sub will send mail to Screenname$ with the subject Subject$ and the message ' Message$ with the attachments in the Files() array. Here are some examples: ' This example will send 1 file to Screenname$. ' Dim Files(1&) ' Files(1&) = "c:\myfolder\myfile.txt" ' Call SendMailWithAttachments(Screenname$, "my subject", "my message", 1&, Files) ' This example will send 3 files to Screenname$. ' Dim Files(3&) ' Files(1&) = "c:\myfolder\myfile1.txt" ' Files(2&) = "c:\myfolder\myfile2.txt" ' Files(3&) = "c:\myfolder\myfile3.txt" ' Call SendMailWithAttachments(Screenname$, "my subject", "my message", 3&, Files) Dim AOLFrame As Long, AOLToolbar As Long, AOLToolbar2 As Long, AOLChildVis As Long Dim AOLIcon As Long, MDIClient As Long, AOLChild As Long, AttachWndVis As Long Dim AOLEdit As Long, RICHCNTL As Long, i As Long, AOLModal As Long Dim AttachWnd As Long, Edit As Long, Button As Long, AOLModVis As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) AOLToolbar& = FindWindowEx(AOLFrame&, 0&, "AOL Toolbar", vbNullString) AOLToolbar2& = FindWindowEx(AOLToolbar&, 0&, "_AOL_Toolbar", vbNullString) AOLIcon& = FindWindowEx(AOLToolbar2&, 0&, "_AOL_Icon", vbNullString) AOLIcon& = FindWindowEx(AOLToolbar2&, AOLIcon&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Write Mail") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& Call Pause(0.1) AOLEdit& = FindWindowEx(AOLChild&, 0&, "_AOL_Edit", vbNullString) Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Screenname$) For i& = 1& To 2& AOLEdit& = FindWindowEx(AOLChild&, AOLEdit&, "_AOL_Edit", vbNullString) Next i& Call SendMessageByString(AOLEdit&, WM_SETTEXT, 0&, Subject$) RICHCNTL& = FindWindowEx(AOLChild&, 0&, "RICHCNTL", vbNullString) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 12& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Attachments") AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& For i& = 1& To FileCount& AOLModal& = FindWindow("_AOL_Modal", "Attachments") AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AttachWnd& = FindWindow("#32770", "Attach") AttachWndVis& = IsWindowVisible(AttachWnd&) Call Pause(0.1) Loop Until AttachWndVis& = 1& Edit& = FindWindowEx(AttachWnd&, 0&, "Edit", vbNullString) Call SendMessageByString(Edit&, WM_SETTEXT, 0&, Files(i&)) Button& = FindWindowEx(AttachWnd&, 0&, "Button", vbNullString) Button& = FindWindowEx(AttachWnd&, Button&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AttachWnd& = FindWindow("#32770", "Attach") AttachWndVis& = IsWindowVisible(AttachWnd&) Call Pause(0.1) Loop Until AttachWndVis& = 0& Call Pause(0.1) Next i& Call Pause(0.1) AOLModal& = FindWindow("_AOL_Modal", "Attachments") AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLModal&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Attachments") AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 0& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 13& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call Pause(0.1) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub SendToChat(Message As String) ' This sub will send Message$ to the chatroom. Here's an example: ' Call SendToChat("Hello world!") Dim RICHCNTL As Long, TextLen As Long, RICHCNTLTxt As String RICHCNTL& = FindWindowEx(FindChatWnd(), 0&, "RICHCNTL", vbNullString) RICHCNTL& = FindWindowEx(FindChatWnd(), RICHCNTL&, "RICHCNTL", vbNullString) TextLen& = SendMessage(RICHCNTL&, WM_GETTEXTLENGTH, 0&, 0&) RICHCNTLTxt$ = String(TextLen&, 0&) Call SendMessageByString(RICHCNTL&, WM_GETTEXT, TextLen& + 1&, RICHCNTLTxt$) Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, Message$) Call SendMessageByNum(RICHCNTL&, WM_CHAR, 13&, 0&) If Len(RICHCNTLTxt$) <> 0& Then Call SendMessageByString(RICHCNTL&, WM_SETTEXT, 0&, RICHCNTLTxt$) End Sub Public Sub SetAOLParent(hWnd As Long) ' This sub will set the parent of a hWnd to AOL's MDI Client. The ' following example will set Form1's parent to AOL's MDI Client. ' Call SetAOLParent(Form1) Dim AOLFrame As Long, MDIClient As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Call SetParent(hWnd&, MDIClient&) End Sub Public Sub SetChatPreferences(NotifyArrive As Boolean, NotifyLeave As Boolean, DoubleSpace As Boolean, Alphabetize As Boolean, ChatSounds As Boolean) ' This sub will set the user's chat preferences. Here's an example... ' Call SetChatPreferences(True, True, True, True, True) Dim AOLModal As Long, ModalVis As Long, AOLCheckbox As Long, AOLIcon As Long Dim AOLChild As Long, AOLChildVis As Long, AOLFrame As Long, MDIClient As Long Call RunPopupMenu(6&, 3&, False) AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Preferences") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Chat Preferences") ModalVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until ModalVis& = 1& AOLCheckbox& = FindWindowEx(AOLModal&, 0&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, NotifyArrive, 0&) AOLCheckbox& = FindWindowEx(AOLModal&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, NotifyLeave, 0&) AOLCheckbox& = FindWindowEx(AOLModal&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, DoubleSpace, 0&) AOLCheckbox& = FindWindowEx(AOLModal&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, Alphabetize, 0&) AOLCheckbox& = FindWindowEx(AOLModal&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, ChatSounds, 0&) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) DoEvents Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Chat Preferences") Loop Until AOLModal& = 0& Call PostMessage(AOLChild&, WM_CLOSE, 0&, 0&) End Sub Public Sub SetCheckbox(Checkbox As Long, CheckBoxValue As Boolean) ' This sub will set a checkbox to True or False. Here's an example... ' Note: This example set's Checkbox& to True. ' Checkbox& = [Checkbox's handle.] ' Call SetCheckBox(Checkbox&, True) Call SendMessage(Checkbox&, BM_SETCHECK, CheckBoxValue, 0&) End Sub Public Sub SetMailPreferences() ' This sub will set your mail preferences to Close Mail After Sent & To Not Confirm Mail After Sent. ' Here's an example on how to call this sub: ' Call SetMailPreferences Dim AOLModal As Long, ModalVis As Long, AOLCheckbox As Long, AOLIcon As Long Call RunPopupMenu(3&, 7&, False) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Mail Preferences") ModalVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until ModalVis& = 1& AOLCheckbox& = FindWindowEx(AOLModal&, 0&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, False, 0&) AOLCheckbox& = FindWindowEx(AOLModal&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Call SendMessage(AOLCheckbox&, BM_SETCHECK, True, 0&) AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Mail Preferences") Loop Until AOLModal& = 0& End Sub Public Sub SetText(hWnd As Long, Text As String) ' This sub will send text to a field. The following example ' will send text to the AOL chat text field. ' RICHCNTL& = FindWindowEx(FindChatWnd(), 0&, "RICHCNTL", vbNullString) ' RICHCNTL& = FindWindowEx(FindChatWnd(), RICHCNTL&, "RICHCNTL", vbNullString) ' Text$ = [Text to send to the field.] ' Call SetText(RICHCNTL&, Text$) Call SendMessageByString(hWnd&, WM_SETTEXT, 0&, Text$) End Sub Public Sub SignOffAOL() ' This sub will sign the user off of AOL. Here's an example... ' Call SignOffAOL Call RunMenuByString("&Sign Off") End Sub Public Sub SignOnAOL() ' This sub will click the 'Sign On' button on the Sign On window. Here's an example: ' Call SignOnAOL Dim AOLFrame As Long, MDIClient As Long, SignOn As Long Dim Goodbye As Long, AOLIcon As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) SignOn& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Sign On") Goodbye& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Goodbye from America Online!") If SignOn& Then AOLChild& = SignOn&: If Goodbye& Then AOLChild& = Goodbye& AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call SendMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call SendMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub SignOnGuest(Screenname As String, Password As String) ' This sub will fill out the Guest Sign On window and ' click 'OK'. Here's an example... ' Screenname$ = [Screenname to sign on with.] ' Password$ = [Password to try.] ' Call SignOnGuest(Screenname$, Password$) Dim AOLEdit As Long, AOLIcon As Long If FindGuestWnd() = 0& Then Exit Sub AOLEdit& = FindWindowEx(FindGuestWnd(), 0&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Screenname$) AOLEdit& = FindWindowEx(FindGuestWnd(), AOLEdit&, "_AOL_Edit", vbNullString) Call SetText(AOLEdit&, Password$) DoEvents AOLIcon& = FindWindowEx(FindGuestWnd(), 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) End Sub Public Sub StartGhosting() ' This sub will make you invisible to everyone on AOL. ' Including IM's and Buddy Lists. Here's an example... ' Call StartGhosting Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim AOLIcon As Long, i As Long, BuddyLists As Long, BuddyListsVis As Long Dim PrivacyPrefs As Long, PrivacyPrefsVis As Long, AOLCheckbox As Long Dim MsgWnd As Long, MsgWndVis As Long, Button As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon& = FindWindowEx(BuddyLists&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents PrivacyPrefs& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Privacy Preferences") PrivacyPrefsVis& = IsWindowVisible(PrivacyPrefs&) Call Pause(0.1) Loop Until PrivacyPrefsVis& = 1& AOLCheckbox& = FindWindowEx(PrivacyPrefs&, 0&, "_AOL_Checkbox", vbNullString) For i& = 1& To 4& AOLCheckbox& = FindWindowEx(PrivacyPrefs&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Next i& Call PostMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) AOLCheckbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Checkbox", vbNullString) For i& = 1& To 6& AOLCheckbox& = FindWindowEx(AOLChild&, AOLCheckbox&, "_AOL_Checkbox", vbNullString) Next i& Call PostMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) AOLIcon& = FindWindowEx(PrivacyPrefs&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(PrivacyPrefs&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgWnd& = FindWindow("#32770", vbNullString) MsgWndVis& = IsWindowVisible(MsgWnd&) Call Pause(0.1) Loop Until MsgWndVis& = 1& Button& = FindWindowEx(MsgWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgWnd& = FindWindow("#32770", vbNullString) MsgWndVis& = IsWindowVisible(MsgWnd&) Call Pause(0.1) Loop Until MsgWndVis& = 0& BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call PostMessage(BuddyLists&, WM_CLOSE, 0&, 0&) End Sub Public Sub StopGhosting() ' This sub will make you visible to everyone on AOL. ' Including IM's and Buddy Lists. Here's an example... ' Call StopGhosting Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim AOLIcon As Long, i As Long, BuddyLists As Long, BuddyListsVis As Long Dim PrivacyPrefs As Long, PrivacyPrefsVis As Long, AOLCheckbox As Long Dim MsgWnd As Long, MsgWndVis As Long, Button As Long AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") If AOLChild& = 0& Then Call RunPopupMenu(10&, 7&, False) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Buddy List Window") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& End If AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 2& AOLIcon& = FindWindowEx(AOLChild&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") BuddyListsVis& = IsWindowVisible(BuddyLists&) Call Pause(0.1) Loop Until BuddyListsVis& = 1& AOLIcon& = FindWindowEx(BuddyLists&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 4& AOLIcon& = FindWindowEx(BuddyLists&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents PrivacyPrefs& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Privacy Preferences") PrivacyPrefsVis& = IsWindowVisible(PrivacyPrefs&) Call Pause(0.1) Loop Until PrivacyPrefsVis& = 1& AOLCheckbox& = FindWindowEx(PrivacyPrefs&, 0&, "_AOL_Checkbox", vbNullString) Call PostMessage(AOLCheckbox&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLCheckbox&, WM_LBUTTONUP, 0&, 0&) AOLIcon& = FindWindowEx(PrivacyPrefs&, 0&, "_AOL_Icon", vbNullString) For i& = 1& To 3& AOLIcon& = FindWindowEx(PrivacyPrefs&, AOLIcon&, "_AOL_Icon", vbNullString) Next i& Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgWnd& = FindWindow("#32770", vbNullString) MsgWndVis& = IsWindowVisible(MsgWnd&) Call Pause(0.1) Loop Until MsgWndVis& = 1& Button& = FindWindowEx(MsgWnd&, 0&, "Button", vbNullString) Call PostMessage(Button&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(Button&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents MsgWnd& = FindWindow("#32770", vbNullString) MsgWndVis& = IsWindowVisible(MsgWnd&) Call Pause(0.1) Loop Until MsgWndVis& = 0& BuddyLists& = FindWindowEx(MDIClient&, 0&, "AOL Child", AOLScreenname() & "'s Buddy Lists") Call PostMessage(BuddyLists&, WM_CLOSE, 0&, 0&) End Sub Public Sub SwitchScreenname(Screenname As String) ' This sub will sign off the current screenname, and log on ' to a different screenname on the user's account. Here's ' an example... ' Screenname$ = [Screenname to log on with.] ' Call SwitchScreenname(Screenname$) Dim AOLFrame As Long, MDIClient As Long, AOLChild As Long, AOLChildVis As Long Dim AOLListbox As Long, lpdwProcessId As Long, hProcess As Long, Item As String Dim ItemData As Long, lpNumberOfBytesWritten As Long, Dest As Long, Index As Long Dim AOLIcon As Long, AOLModal As Long, AOLModVis As Long On Error Resume Next Call RunMenuByString("Switch Scree&n Name") AOLFrame& = FindWindow("AOL Frame25", vbNullString) MDIClient& = FindWindowEx(AOLFrame&, 0&, "MDIClient", vbNullString) Do: DoEvents AOLChild& = FindWindowEx(MDIClient&, 0&, "AOL Child", "Switch Screen Names") AOLChildVis& = IsWindowVisible(AOLChild&) Call Pause(0.1) Loop Until AOLChildVis& = 1& AOLListbox& = FindWindowEx(AOLChild&, 0&, "_AOL_Listbox", vbNullString) Call GetWindowThreadProcessId(AOLListbox&, lpdwProcessId&) hProcess& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, lpdwProcessId&) For Index& = 0 To SendMessageByNum(AOLListbox&, LB_GETCOUNT, 0&, 0&) - 1& Item$ = String(4&, vbNullChar) ItemData& = SendMessage(AOLListbox&, LB_GETITEMDATA, Index&, 0&) ItemData& = ItemData& + 24& Call ReadProcessMemory(hProcess&, ItemData&, Item$, 4&, lpNumberOfBytesWritten&) Call CopyMemory(Dest&, ByVal Item$, 4&) Dest& = Dest& + 6& Item$ = String(100&, vbNullChar) Call ReadProcessMemory(hProcess&, Dest&, Item$, 100&, lpNumberOfBytesWritten&) Item$ = Trim(Left(Item$, InStr(Item$, vbNullChar) - 1&)) If InStr(LCase(Item$), LCase(Screenname$)) Then Call SendMessage(AOLListbox&, LB_SETCURSEL, Index&, 0&): Exit For Next Index& Call CloseHandle(hProcess&) Call Pause(0.25) AOLIcon& = FindWindowEx(AOLChild&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Switch Screen Name") AOLModVis& = IsWindowVisible(AOLModal&) Call Pause(0.1) Loop Until AOLModVis& = 1& AOLIcon& = FindWindowEx(AOLModal&, 0&, "_AOL_Icon", vbNullString) Call PostMessage(AOLIcon&, WM_LBUTTONDOWN, 0&, 0&) Call PostMessage(AOLIcon&, WM_LBUTTONUP, 0&, 0&) Do: DoEvents AOLModal& = FindWindow("_AOL_Modal", "Switch Screen Name") Loop Until AOLModal& = 0& End Sub Public Sub TurnIMsOff() ' This sub will turn your Instant Message's off. Here's an example on how to call this sub. ' Call TurnIMsOff Call SendInstantMessage("$im_off", " ", True) End Sub Public Sub TurnIMsOn() ' This sub will turn your Instant Message's on. Here's an example on how to call this sub. ' Call TurnIMsOn Call SendInstantMessage("$im_on", " ", True) End Sub Public Sub UnHideWindow(hWnd As Long) ' This sub will UnHide a window. The following ' example will UnHide AOL. ' AOLFrame& = FindWindow("AOL Frame25", vbNullString) ' Call UnHideWindow(AOLFrame&) Call ShowWindow(hWnd&, SW_SHOW) End Sub Public Sub UnIgnoreScreenname(Screenname As String) ' This sub will unignore IM's from Screenname$. Here's an example... ' Screenname$ = [Screenname to unignore IM's from.] Call SendInstantMessage("$im_on " & Screenname$, " ", True) End Sub Public Sub UnUpChat() ' This sub will UnUp-Chat. In other words, it will disable AOL, ' and enable the Upload winodw. Here's an example... ' Call UnUpChat Call EnableWnd(FindUploadWnd()) Call NormalizeWindow(FindUploadWnd()) Call DisableWnd(FindWindowEx("AOL Frame25", vbNullString)) End Sub Public Sub UpChat() ' This sub will up-chat. In other words, it will enable AOL, ' and disable the Upload window. Here's an example... ' Call UpChat Call DisableWnd(FindUploadWnd()) Call MinimizeWindow(FindUploadWnd()) Call EnableWnd(FindWindowEx("AOL Frame25", vbNullString)) End Sub Public Sub ViewBuddyList() ' This sub will open the user's buddy list. Here's an example... ' Call ViewBuddyList Call RunPopupMenu(10&, 7&, False) End Sub Public Sub WaitForComboboxToLoad(hWnd As Long) ' This sub will wait for all the items to load in a combobox. Here's an example... ' hWnd& = [Handle of combobox.] ' Call WaitForComboboxToLoad(hWnd&) Dim ListCount1 As Long, ListCount2 As Long, ListCount3 As Long Do: DoEvents ListCount1& = SendMessage(hWnd&, CB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount2& = SendMessage(hWnd&, CB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount3& = SendMessage(hWnd&, CB_GETCOUNT, 0&, 0&) Loop Until ListCount2& = ListCount1& And ListCount3& = ListCount1& End Sub Public Sub WaitForListToLoad(hWnd As Long) ' This sub will wait for all the items to load in a listbox (or tree). Here's an example... ' hWnd& = [Handle of listbox.] ' Call WaitForListToLoad(hWnd&) Dim ListCount1 As Long, ListCount2 As Long, ListCount3 As Long Do: DoEvents ListCount1& = SendMessage(hWnd&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount2& = SendMessage(hWnd&, LB_GETCOUNT, 0&, 0&) Call Pause(0.25) ListCount3& = SendMessage(hWnd&, LB_GETCOUNT, 0&, 0&) Loop Until ListCount2& = ListCount1& And ListCount3& = ListCount1& End Sub Public Sub WaitForTextToLoad(hWnd As Long) ' This sub will wait for all the text to load in a text field. Here's an example... ' hWnd& = [Handle of text field.] ' Call WaitForTextToLoad(hWnd&) Dim Count1 As Long, Count2 As Long, Count3 As Long Do: DoEvents Count1& = Len(GetText(hWnd&)) Call Pause(0.5) Count2& = Len(GetText(hWnd&)) Call Pause(0.5) Count3& = Len(GetText(hWnd&)) Loop Until Count2& = Count1& And Count3& = Count1& And Count3& <> 0& End Sub Public Sub WriteToINI(AppName As String, KeyName As String, KeyValue As String, FileName As String) ' This function will write to an INI file. Here's an example... ' WriteToINI("My App", "My Keyname", "My KeyValue", "myfile.ini") Call WritePrivateProfileString(AppName$, KeyName$, KeyValue$, FileName$) End Sub