- Konu Yazar
- #1
Option Explicit
Public keyboard As Long
Private Type SECURITY_ATTRIBUTES
nLength As Long
lpSecurityDescriptor As Long
bInheritHandle As Long
End Type
Private Const MEM_COMMIT = &H1000
Private Const MEM_RELEASE = &H8000&
Private Const PAGE_READWRITE = &H4&
Private Const INFINITE = &HFFFF
Public Const MAILSLOT_NO_MESSAGE As Long = (-1)
Public Declare Function GetTickCount Lib "kernel32" () As Long 'apidir bunu ekle modulde yukariya
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function ReadProcessMem Lib "kernel32" Alias "ReadProcessMemory" (ByVal hProcess As Long, ByVal lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Public Declare Function WriteProcessMem Lib "kernel32" Alias "WriteProcessMemory" (ByVal hProcess As Long, ByVal lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Private Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Long) As Long
Private Declare Function CreateMailslot Lib "kernel32" Alias "CreateMailslotA" (ByVal lpName As String, ByVal nMaxMessageSize As Long, ByVal lReadTimeout As Long, lpSecurityAttributes As Any) As Long
Private Declare Function GetMailslotInfo Lib "kernel32" (ByVal hMailSlot As Long, lpMaxMessageSize As Long, lpNextSize As Long, lpMessageCount As Long, lpReadTimeout As Long) As Long
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Private Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As Long) As Long
Private Declare Function CreateRemoteThread Lib "kernel32" (ByVal hProcess As Long, lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal dwStackSize As Long, lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadID As Long) As Long
Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Private Declare Function VirtualFreeEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, ByVal dwSize As Long, ByVal dwFreeType As Long) As Long
Private Declare Function VirtualAllocEx Lib "kernel32" (ByVal hProcess As Long, ByVal lpAddress As Long, ByVal dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Private Declare Function GetPrivateProfileSection Lib "kernel32" Alias "GetPrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
Private 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
Private 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
Private Declare Function WritePrivateProfileSection Lib "kernel32" Alias "WritePrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpString As String, ByVal lpFileName As String) As Long
Private 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
Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Public Declare Function GetModuleInformation Lib "PSAPI.DLL" (ByVal hProcess As Long, ByVal hModule As Long, lpmodinfo As MODULEINFO, ByVal cb As Long) As Long
Public Declare Function EnumProcessModules Lib "PSAPI.DLL" (ByVal hProcess As Long, ByRef lphModule As Long, ByVal cb As Long, ByRef cbNeeded As Long) As Long
Public Declare Function GetModuleFileNameExA Lib "PSAPI.DLL" (ByVal hProcess As Long, ByVal hModule As Long, ByVal ModuleName As String, ByVal nSize As Long) As Long
Public hexword As String
Private Const PROCESS_ALL_ACCESS = &H1F0FFF
Public Const SWP_NOMOVE = 2
Public Const SWP_NOSIZE = 1
Public Const FLAGS = SWP_NOMOVE Or SWP_NOSIZE
Public Const HWND_TOPMOST = -1
Public Const HWND_NOTOPMOST = -2
Public Const LWA_COLORKEY = 1
Public Const LWA_ALPHA = 2
Public ko As Long
Public Const LWA_BOTH = 3
Public Const WS_EX_LAYERED = &H80000
Public Const GWL_EXSTYLE = -20
Public Timer As Date
Public Diff As Long
Public UseOtocanPot
Public Hook
Public CurrentNation As String
Public class As String
Public UseTimed As Boolean
Public PotionTimer As Date
Public Char As Long
Public TimedTimer As Date
Public AttackTimer As Long
Public AttackDiff As Long
Public TargetTimer As Date
Public TargetDiff As Long
Public TimedDiff As Long
Public PotionDiff As Long
Public PublicWolf As Long
Public UseAutoWolf
Public UseOtomanapot
Public UseAutoAttack
Public UseManaSave
Public Started
Public HealPercent As Long
Public ManaPercent As Long
Public HealType As Long
Public ManaType As Long
Public AttackALL As String
Public mob As Long
Public SellAll As Long
Public BonusFilter As Long
Public MSName
Public MSHandle
Public UseSitAutoAttack
Public UseWallHack
Public durab As Long
Public UseLupineEyes
Public UseAutoSwift
Public UseAutoSell
Public UseAutoLoot
Public CurrentMobHP As Long
Public BoxID
Public itemID
Public AttackNow
Public SecondID
Public ThirdID
Public FourthID
Public FifthID
Public SixthID
Public BoxOpened
Public Exp As Long
Public outack
Public Looting
Public ChatTipi As String
Public RepairID As String
Public ItemSlot As String
Public RecvID As String
Public LastBoxID As Long
Public OpenNextBox As Boolean
Public LastRepair As Date
Public RepairDiff As Long
Public LootBuffer As String
'start declaring autoattack log
Public LastID
Public TargetID As Long
Public MaxEXP As Long
'stop declaring autoattack log
Public ChatTipi1 As Long
Public KO_RCVFNC As Long
Public KO_TITLE As String
Public KO_HANDLE As Long
Public KO_PID As Long
Public KO_PTR_CHR As Long
Public KO_PTR_CHR1 As Long
Public KO_PTR_DLG As Long
Public KO_PTR_PKT As Long
Public KO_SND_FNC As Long
Public KO_RECVHK As Long
Public KO_RCVHKB As Long
Public KO_ADR_CHR As Long
Public KO_ADR_DLG As Long
Public KO_OFF_RTM As Long
Public KO_OFF_NT As Long
Public KO_OFF_CLASS As Long
Public KO_OFF_SWIFT As Long
Public KO_OFF_HP As Long
Public KO_OFF_MAXHP As Long
Public KO_OFF_MP As Long
Public KO_OFF_MAXMP As Long
Public KO_OFF_MOB As Long
Public KO_OFF_WH As Long
Public KO_OFF_SIT As Long
Public KO_OFF_LUP As Long
Public KO_OFF_LUP2 As Long
Public KO_OFF_Y As Long
Public KO_OFF_ID As Long
Public KO_OFF_HD As Long
Public KO_OFF_X As Long
Public KO_OFF_SEL As Long
Public KO_OFF_LUPINE As Long
Public KO_OFF_EXP As Long
Public KO_OFF_MAXEXP As Long
Public KO_OFF_AP As Long
Public KO_OFF_GOLD As Long
Public nation As Long
Public KO_TITLE1 As String
Public DINPUT_Handle As Long
Public DINPUT_lpBaseOfDLL As Long
Public DINPUT_SizeOfImage As Long
Public DINPUT_EntryPoint As Long
Public DINPUT_KEYDMA As Long
Public DINPUT_K_1 As Long
Public DINPUT_K_2 As Long
Public DINPUT_K_3 As Long
Public DINPUT_K_4 As Long
Public DINPUT_K_5 As Long
Public DINPUT_K_6 As Long
Public DINPUT_K_7 As Long
Public DINPUT_K_8 As Long
Public DINPUT_K_Z As Long
Public DINPUT_K_C As Long
Public DINPUT_K_S As Long
Public DINPUT_K_R As Long
Public KO_CHR As Long
Public MP1 As Long
Public Type MODULEINFO
lpBaseOfDLL As Long
SizeOfImage As Long
EntryPoint As Long
End Type
' dll inject komutlari
Public Function HookDI8() As Boolean
Dim Ret As Long
Dim lmodinfo As MODULEINFO
DINPUT_Handle = 0
DINPUT_Handle = FindModuleHandle("dinput8.dll")
Ret = GetModuleInformation(KO_HANDLE, DINPUT_Handle, lmodinfo, Len(lmodinfo))
If Ret <> 0 Then
With lmodinfo
DINPUT_EntryPoint = .EntryPoint
DINPUT_lpBaseOfDLL = .lpBaseOfDLL
DINPUT_SizeOfImage = .SizeOfImage
End With
Else
Exit Function
End If
SetupDInput
HookDI8 = True
End Function
Public Function FindModuleHandle(ModuleName As String) As Long
Dim hModules(1 To 256) As Long
Dim BytesReturned As Long
Dim ModuleNumber As Byte
Dim TotalModules As Byte
Dim FileName As String * 128
Dim ModName As String
EnumProcessModules KO_HANDLE, hModules(1), 1024, BytesReturned
TotalModules = BytesReturned / 4
For ModuleNumber = 1 To TotalModules
GetModuleFileNameExA KO_HANDLE, hModules(ModuleNumber), FileName, 128
ModName = Left(FileName, InStr(FileName, Chr(0)) - 1)
If UCase(Right(ModName, Len(ModuleName))) = UCase(ModuleName) Then
FindModuleHandle = hModules(ModuleNumber)
End If
Next
End Function
Sub SetupDInput()
DINPUT_KEYDMA = FindDInputKeyPtr
If DINPUT_KEYDMA <> 0 Then
DINPUT_K_1 = DINPUT_KEYDMA + 2
DINPUT_K_2 = DINPUT_KEYDMA + 3
DINPUT_K_3 = DINPUT_KEYDMA + 4
DINPUT_K_4 = DINPUT_KEYDMA + 5
DINPUT_K_5 = DINPUT_KEYDMA + 6
DINPUT_K_6 = DINPUT_KEYDMA + 7
DINPUT_K_7 = DINPUT_KEYDMA + 8
DINPUT_K_8 = DINPUT_KEYDMA + 9
DINPUT_K_Z = DINPUT_KEYDMA + 44
DINPUT_K_C = DINPUT_KEYDMA + 46
DINPUT_K_S = DINPUT_KEYDMA + 31
DINPUT_K_R = DINPUT_KEYDMA + 19
End If
End Sub
Function FindDInputKeyPtr() As Long
Dim pBytes() As Byte
Dim pSize As Long
Dim X As Long
pSize = DINPUT_SizeOfImage
ReDim pBytes(1 To pSize)
ReadByteArray DINPUT_lpBaseOfDLL, pBytes, pSize
For X = 1 To pSize - 10
If pBytes(X) = &H57 And pBytes(X + 1) = &H6A And pBytes(X + 2) = &H40 And pBytes(X + 3) = &H33 And pBytes(X + 4) = &HC0 And pBytes(X + 5) = &H59 And pBytes(X + 6) = &HBF Then
FindDInputKeyPtr = Val("&H" & IIf(Len(Hex(pBytes(X + 10))) = 1, "0" & Hex(pBytes(X + 10)), Hex(pBytes(X + 10))) & IIf(Len(Hex(pBytes(X + 9))) = 1, "0" & Hex(pBytes(X + 9)), Hex(pBytes(X + 9))) & IIf(Len(Hex(pBytes(X + 8))) = 1, "0" & Hex(pBytes(X + 8)), Hex(pBytes(X + 8))) & IIf(Len(Hex(pBytes(X + 7))) = 1, "0" & Hex(pBytes(X + 7)), Hex(pBytes(X + 7))))
Exit For
End If
Next
End Function
' Buraya ben yolla yazdim sizde istediginizi yaza bilir siniz.
'ama prejedeki Bütün Yolla yazan yerleri degistirmelisiniz.
Function yolla(pKey As String) As Long
pKey = Strings.UCase(pKey)
Select Case pKey
Case "S"
yolla = DINPUT_K_S
Case "Z"
yolla = DINPUT_K_Z
Case "1"
yolla = DINPUT_K_1
Case "2"
yolla = DINPUT_K_2
Case "3"
yolla = DINPUT_K_3
Case "4"
yolla = DINPUT_K_4
Case "5"
yolla = DINPUT_K_5
Case "6"
yolla = DINPUT_K_6
Case "7"
yolla = DINPUT_K_7
Case "8"
yolla = DINPUT_K_8
Case "C"
yolla = DINPUT_K_C
Case "R"
yolla = DINPUT_K_R
End Select
End Function
Sub WriteByte(Addr As Long, pVal As Byte)
Dim pbw As Long
WriteProcessMem KO_HANDLE, Addr, pVal, 1, pbw
End Sub
Sub ReadByteArray(Addr As Long, pmem() As Byte, pSize As Long)
Dim Value As Byte
ReDim pmem(1 To pSize) As Byte
ReadProcessMem KO_HANDLE, Addr, pmem(1), pSize, 0&
End Sub
' Buraya ben TUS yazdim sizde istediginizi yaza bilir siniz.
'ama prejedeki Bütün TUS yazan yerleri degistirmelisiniz.
Sub Tus(pKey As Long, Optional pTimeMS As Long = 50)
WriteByte pKey, 128
f_Sleep pTimeMS, True
WriteByte pKey, 0
End Sub
Sub f_Sleep(pMS As Long, Optional pDoevents As Boolean = False)
Dim pTime As Long
pTime = GetTickCount
Do While pMS + pTime > GetTickCount
If pDoevents = True Then DoEvents
Loop
End Sub
Public Function ReadLong(Addr As Long) As Long 'read a 4 byte value
Dim Value As Long
ReadProcessMem KO_HANDLE, Addr, Value, 4, 0&
ReadLong = Value
End Function
Public Function ReadFloat(Addr As Long) As Long 'read a float value
Dim Value As Single
ReadProcessMem KO_HANDLE, Addr, Value, 4, 0&
ReadFloat = Value
End Function
Public Function WriteFloat(Addr As Long, Val As Single) 'write a float value
WriteProcessMem KO_HANDLE, Addr, Val, 4, 0&
End Function
Public Function WriteLong(Addr As Long, Val As Long) ' write a 4 byte value
WriteProcessMem KO_HANDLE, Addr, Val, 4, 0&
End Function
Public Function SetTopMostWindow(hwnd As Long, Topmost As Boolean) As Long
If Topmost = True Then 'Make the window topmost
SetTopMostWindow = SetWindowPos(hwnd, HWND_TOPMOST, 0, 0, 0, 0, FLAGS)
Else
SetTopMostWindow = SetWindowPos(hwnd, HWND_NOTOPMOST, 0, 0, 0, 0, FLAGS)
SetTopMostWindow = False
End If
End Function
Public Function ReadIni(FileName As String, Section As String, Key As String) As String
Dim RetVal As String * 255, v As Long
v = GetPrivateProfileString(Section, Key, "", RetVal, 255, FileName)
ReadIni = Left(RetVal, v)
End Function
'writes an Ini string
Public Function WriteIni(FileName As String, Section As String, Key As String, Value As String)
WritePrivateProfileString Section, Key, Value, FileName
End Function
Public Function ConvHEX2ByteArray(pStr As String, pByte() As Byte)
Dim i As Long
Dim j As Long
ReDim pByte(1 To Len(pStr) / 2)
j = LBound(pByte) - 1
For i = 1 To Len(pStr) Step 2
j = j + 1
pByte(j) = CByte("&H" & Mid(pStr, i, 2))
Next
End Function
Public Function WriteByteArray(pAddy As Long, pmem() As Byte, pSize As Long)
WriteProcessMem KO_HANDLE, pAddy, pmem(LBound(pmem)), pSize, 0&
End Function
'start packet handling
Function ExecuteRemoteCode(pCode() As Byte, Optional WaitExecution As Boolean = False) As Long
Dim FuncPtr As Long
Dim hThread As Long, ThreadID As Long, Ret As Long
Dim SE As SECURITY_ATTRIBUTES
SE.nLength = Len(SE)
SE.bInheritHandle = False
ExecuteRemoteCode = 0
FuncPtr = VirtualAllocEx(KO_HANDLE, 0, 1024, MEM_COMMIT, PAGE_READWRITE)
If FuncPtr <> 0 Then
WriteByteArray FuncPtr, pCode, UBound(pCode) - LBound(pCode) + 1
hThread = CreateRemoteThread(ByVal KO_HANDLE, SE, 0, ByVal FuncPtr, 0&, 0&, ThreadID)
If hThread Then
Ret = WaitForSingleObject(hThread, INFINITE)
ExecuteRemoteCode = ThreadID
End If
CloseHandle hThread
Ret = VirtualFreeEx(KO_HANDLE, FuncPtr, 0, MEM_RELEASE)
End If
End Function
Function SendPackets(pPacket() As Byte)
Dim BytesAddr As Long
Dim pSize As Long
Dim pCode() As Byte
'60 PUSHAD
'A1 84898100 MOV EAX,DWORD PTR DS:[818984]
'8B0D 84898100 MOV ECX,DWORD PTR DS:[818984]
'68 dword(packet size)
'68 dword(BytesAddr) 'call packetsize
'BF C0184500 MOV EDI,_KnightO.004518C0 -> entry address
'FFD7
'61
'C3
'KO_PTR_PKT = &H818984 'packet function
'KO_SND_FNC = &H451B80 'entry adress
pSize = UBound(pPacket) - LBound(pPacket) + 1
BytesAddr = VirtualAllocEx(KO_HANDLE, 0, 1024, MEM_COMMIT, PAGE_READWRITE)
If BytesAddr <> 0 Then
WriteByteArray BytesAddr, pPacket, pSize
ConvHEX2ByteArray "60A1" & AlignDWORD(KO_PTR_PKT) & "8B0D" & AlignDWORD(KO_PTR_PKT) & "68" & AlignDWORD(pSize) & "68" & AlignDWORD(BytesAddr) & "BF" & AlignDWORD(KO_SND_FNC) & "FFD761C3", pCode
ExecuteRemoteCode pCode, True
End If
VirtualFreeEx KO_HANDLE, BytesAddr, 0, MEM_RELEASE&
End Function
'
alttaymis zate:d
Function AlignDWORD(pParam As Long) As String
Dim HiW As Integer
Dim LoW As Integer
Dim HiBHiW As Byte
Dim HiBLoW As Byte
Dim LoBHiW As Byte
Dim LoBLoW As Byte
HiW = HiWord(pParam)
LoW = LoWord(pParam)
HiBHiW = HiByte(HiW)
HiBLoW = HiByte(LoW)
LoBHiW = LoByte(HiW)
LoBLoW = LoByte(LoW)
AlignDWORD = IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW))
End Function 'sansa bak 8 mis zate
1
Function AlignDWORD8(pParam As Long) As String
Dim HiW As Integer
Dim LoW As Integer
Dim HiBHiW As Byte
Dim HiBLoW As Byte
Dim LoBHiW As Byte
Dim LoBLoW As Byte
HiW = HiWord(pParam)
LoW = LoWord(pParam)
HiBHiW = HiByte(HiW)
HiBLoW = HiByte(LoW)
LoBHiW = LoByte(HiW)
LoBLoW = LoByte(LoW)
AlignDWORD8 = IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW)) & _
IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW))
End Function
Public Function HiByte(ByVal wParam As Integer) As Byte
HiByte = (wParam And &HFF00&) \ (&H100)
End Function
Public Function LoByte(ByVal wParam As Integer) As Byte
LoByte = wParam And &HFF&
End Function
Function LoWord(DWord As Long) As Integer
If DWord And &H8000& Then '
LoWord = DWord Or &HFFFF0000
Else
LoWord = DWord And &HFFFF&
End If
End Function
Function HiWord(DWord As Long) As Integer
HiWord = (DWord And &HFFFF0000) \ &H10000
End Function
Public Function LogFile(sStr As String)
Open CurDir & "\Log.txt" For Append As #1
Print #1, ";==> " & Time & " " & sStr & " ;<=="
Close #1
End Function
Public Function AttachKO() As Boolean
Dim inject As Boolean
If FindWindow(vbNullString, KO_TITLE) Then
MSName = "\\.\mailslot\ByS0x" & Hex(GetTickCount)
GetWindowThreadProcessId FindWindow(vbNullString, KO_TITLE), KO_PID
KO_HANDLE = OpenProcess(PROCESS_ALL_ACCESS, False, KO_PID)
If KO_HANDLE = 0 Then
MsgBox ("Cannot get handle from KO(" & KO_PID & ").")
AttachKO = False
End If
Hook = HookDI8 'HooKDI8 dinput8.dll degerini kontrol ettiriyoruz
If Hook = False Then 'eger hook false ise
AttachKO = False 've attachko muzu false ediyoruz.
MsgBox "Dinput8.dll Yüklenemiyor.Koxpun Bulundupu Klasöre Dinput8.dll atiniz.", vbDefaultButton2, "Dikkat"
End If
MSHandle = EstablishMailSlot(MSName) 'mail slotumuzu açiyoruz
If MSHandle = 0 Then End 'eger MSHandle esitse sifir a demekki mesaj gelmiyor Ko dan sonlandir diyoruz.
If KO_PID = 0 Then End 'Ko nun pid degeride 0 a esitse gene sonlandiriyoruz programimizi
'Evet iste burasi çok önemli mail slotu için ko nun exe sinde bazi degisiklik yapiyor
'MsgBox (KO_PID)
'prevent iexplore to be launched on exit
'Dim pBytess() As Byte
'00670A23 E9 09010000 JMP KnightOn.00670B31
'00670A28 90 NOP
'ConvHEX2ByteArray "E90901000090", pBytess ' patch hackshield
'WriteByteArray &H670A23, pBytess, UBound(pBytess) - LBound(pBytess) + 1
AttachKO = True
Else
MsgBox "Ilk Önce Oyunu Acin", vbDefaultButton1, "Dikkat"
End If
End Function
Public Function EstablishMailSlot(ByVal MailSlotName As String, Optional MaxMessageSize As Long = 0, Optional ReadTimeOut As Long = 50) As Long
EstablishMailSlot = CreateMailslot(MailSlotName, MaxMessageSize, ReadTimeOut, ByVal 0&)
End Function
Function LoadOffsets()
KO_TITLE = Form1.Text1.Text
KO_PTR_CHR = &HB6E3BC
KO_PTR_DLG = &HB6FC94
KO_PTR_PKT = &HB6FC60 'packet function
KO_SND_FNC = &H473870 'entry adress
'KO_RECVHK = &HB6EC74 '5C5193
'KO_RCVHKB = &H5C519A '5C519A
KO_OFF_SWIFT = 1582
KO_OFF_CLASS = 1416
KO_OFF_NT = 1412
KO_OFF_HP = 1428
KO_OFF_MAXHP = 1424
KO_OFF_MP = 2364
KO_OFF_MAXMP = 2360
KO_OFF_SIT = 2790
KO_OFF_MOB = 1332
KO_OFF_WH = 1432
KO_OFF_Y = 184
KO_OFF_X = 176
KO_OFF_LUP = 3204
KO_OFF_LUP2 = 2800
KO_OFF_EXP = 2072
KO_OFF_MAXEXP = 2068
KO_OFF_AP = 2136
KO_OFF_GOLD = 2064
KO_OFF_ID = 1383
KO_OFF_HD = 1300
nation = &H584
ko = ReadLong(KO_PTR_CHR)
End Function
Sub Skill(skillid As String)
Dim ID As String
Dim ID1 As String
Dim ID2 As String
Dim IDs As Long
Dim skillid1
Dim skillid2
Dim skillid3
Dim skillhex As String
Dim skillid4 As String
skillhex = Hex(skillid)
skillid1 = Mid$(skillhex, 4, 6)
skillid2 = Mid$(skillhex, 2, 2)
skillid3 = Mid$(skillhex, 1, 1)
IDs = ReadLong(KO_ADR_CHR + KO_OFF_ID)
ID = AlignDWORD(IDs)
ID1 = Strings.Mid(ID, 3, 2)
ID2 = Strings.Mid(ID, 5, 2)
Dim pBytes(1 To 18) As Byte
pBytes(1) = &H31
pBytes(2) = &H3
pBytes(3) = "&H" & skillid1
pBytes(4) = "&H" & skillid2
pBytes(5) = "&H" & skillid3
pBytes(6) = &H0
pBytes(7) = "&H" & ID1
pBytes(8) = "&H" & ID2
pBytes(9) = "&H" & ID1
pBytes(10) = "&H" & ID2
pBytes(11) = &H0
pBytes(12) = &H0
pBytes(13) = &H0
pBytes(14) = &H0
pBytes(15) = &H0
pBytes(16) = &H0
pBytes(17) = &H0
pBytes(18) = &H0
SendPackets pBytes
PotionTimer = Now
End Sub
Private Function ReadMessage(MailMessage As String, MessagesLeft As Long)
Dim lBytesRead As Long
Dim lNextMsgSize As Long
Dim lpBuffer As String
ReadMessage = False
Call GetMailslotInfo(MSHandle, ByVal 0&, lNextMsgSize, MessagesLeft, ByVal 0&)
If MessagesLeft > 0 And lNextMsgSize <> MAILSLOT_NO_MESSAGE Then
lBytesRead = 0
lpBuffer = String$(lNextMsgSize, Chr$(0))
Call ReadFile(MSHandle, ByVal lpBuffer, Len(lpBuffer), lBytesRead, ByVal 0&)
If lBytesRead <> 0 Then
MailMessage = Left(lpBuffer, lBytesRead)
ReadMessage = True
Call GetMailslotInfo(MSHandle, ByVal 0&, lNextMsgSize, MessagesLeft, ByVal 0&)
End If
End If
End Function
Private Function CheckForMessages(MessageCount As Long)
Dim lMsgCount As Long
Dim lNextMsgSize As Long
CheckForMessages = False
GetMailslotInfo MSHandle, ByVal 0&, lNextMsgSize, lMsgCount, ByVal 0&
MessageCount = lMsgCount
CheckForMessages = True
End Function
Private Function HexString(EvalString As String) As String
Dim intStrLen As Integer
Dim intLoop As Integer
Dim strHex As String
EvalString = Trim(EvalString)
intStrLen = Len(EvalString)
For intLoop = 1 To intStrLen
strHex = strHex & Hex(Asc(Mid(EvalString, intLoop, 1)))
Next
hexword = strHex
End Function
Function Notice(NoticeYazi As String)
Dim pStr As String
Dim pBytes() As Byte
HexString NoticeYazi
If Form1.Combo3.ListIndex = 0 Then
pStr = "10" + "01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 1 Then
pStr = "10" + "05" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 2 Then
pStr = "11" + "03" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 3 Then
pStr = "11" + "06" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 4 Then
pStr = "11" + "0E" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 1 Then
pStr = "11" + "0F" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
End If
End If
End If
End If
End If
End If
End Function
Modül ile kullanılabilinecek fonksiyonlar :
GM'leri görme (denenmedi)
Oto Lup
Oto Kutu
Tarot Hack +1 HP
Süper Okçu Yapmak
Stat Sıfırlama
Start Butonu
Skill Sıfırlama
Sınırsız Swift
Seri CS
Ölünce Pc Kapat
Ölünce Oyunu Kapat
Oto TS
Oto Rpr
Oto Party
Oto Hp-Mp Çektirme
Irk Hack
Hazzard
Oto Ft Giriş
Hp Düşerse Town at
Char Sabitlemek
Char Gizlemek
Atak Başlat
Wall Hack
Koxpu Oyuna Bağlamak
Alt-Tab Ekle
KnightOnline.exe Yolu Göstermek
Public keyboard As Long
Private Type SECURITY_ATTRIBUTES
nLength As Long
lpSecurityDescriptor As Long
bInheritHandle As Long
End Type
Private Const MEM_COMMIT = &H1000
Private Const MEM_RELEASE = &H8000&
Private Const PAGE_READWRITE = &H4&
Private Const INFINITE = &HFFFF
Public Const MAILSLOT_NO_MESSAGE As Long = (-1)
Public Declare Function GetTickCount Lib "kernel32" () As Long 'apidir bunu ekle modulde yukariya
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function ReadProcessMem Lib "kernel32" Alias "ReadProcessMemory" (ByVal hProcess As Long, ByVal lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Public Declare Function WriteProcessMem Lib "kernel32" Alias "WriteProcessMemory" (ByVal hProcess As Long, ByVal lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Private Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Long) As Long
Private Declare Function CreateMailslot Lib "kernel32" Alias "CreateMailslotA" (ByVal lpName As String, ByVal nMaxMessageSize As Long, ByVal lReadTimeout As Long, lpSecurityAttributes As Any) As Long
Private Declare Function GetMailslotInfo Lib "kernel32" (ByVal hMailSlot As Long, lpMaxMessageSize As Long, lpNextSize As Long, lpMessageCount As Long, lpReadTimeout As Long) As Long
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Private Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As Long) As Long
Private Declare Function CreateRemoteThread Lib "kernel32" (ByVal hProcess As Long, lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal dwStackSize As Long, lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadID As Long) As Long
Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Private Declare Function VirtualFreeEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, ByVal dwSize As Long, ByVal dwFreeType As Long) As Long
Private Declare Function VirtualAllocEx Lib "kernel32" (ByVal hProcess As Long, ByVal lpAddress As Long, ByVal dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Private Declare Function GetPrivateProfileSection Lib "kernel32" Alias "GetPrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
Private 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
Private 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
Private Declare Function WritePrivateProfileSection Lib "kernel32" Alias "WritePrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpString As String, ByVal lpFileName As String) As Long
Private 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
Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Public Declare Function GetModuleInformation Lib "PSAPI.DLL" (ByVal hProcess As Long, ByVal hModule As Long, lpmodinfo As MODULEINFO, ByVal cb As Long) As Long
Public Declare Function EnumProcessModules Lib "PSAPI.DLL" (ByVal hProcess As Long, ByRef lphModule As Long, ByVal cb As Long, ByRef cbNeeded As Long) As Long
Public Declare Function GetModuleFileNameExA Lib "PSAPI.DLL" (ByVal hProcess As Long, ByVal hModule As Long, ByVal ModuleName As String, ByVal nSize As Long) As Long
Public hexword As String
Private Const PROCESS_ALL_ACCESS = &H1F0FFF
Public Const SWP_NOMOVE = 2
Public Const SWP_NOSIZE = 1
Public Const FLAGS = SWP_NOMOVE Or SWP_NOSIZE
Public Const HWND_TOPMOST = -1
Public Const HWND_NOTOPMOST = -2
Public Const LWA_COLORKEY = 1
Public Const LWA_ALPHA = 2
Public ko As Long
Public Const LWA_BOTH = 3
Public Const WS_EX_LAYERED = &H80000
Public Const GWL_EXSTYLE = -20
Public Timer As Date
Public Diff As Long
Public UseOtocanPot
Public Hook
Public CurrentNation As String
Public class As String
Public UseTimed As Boolean
Public PotionTimer As Date
Public Char As Long
Public TimedTimer As Date
Public AttackTimer As Long
Public AttackDiff As Long
Public TargetTimer As Date
Public TargetDiff As Long
Public TimedDiff As Long
Public PotionDiff As Long
Public PublicWolf As Long
Public UseAutoWolf
Public UseOtomanapot
Public UseAutoAttack
Public UseManaSave
Public Started
Public HealPercent As Long
Public ManaPercent As Long
Public HealType As Long
Public ManaType As Long
Public AttackALL As String
Public mob As Long
Public SellAll As Long
Public BonusFilter As Long
Public MSName
Public MSHandle
Public UseSitAutoAttack
Public UseWallHack
Public durab As Long
Public UseLupineEyes
Public UseAutoSwift
Public UseAutoSell
Public UseAutoLoot
Public CurrentMobHP As Long
Public BoxID
Public itemID
Public AttackNow
Public SecondID
Public ThirdID
Public FourthID
Public FifthID
Public SixthID
Public BoxOpened
Public Exp As Long
Public outack
Public Looting
Public ChatTipi As String
Public RepairID As String
Public ItemSlot As String
Public RecvID As String
Public LastBoxID As Long
Public OpenNextBox As Boolean
Public LastRepair As Date
Public RepairDiff As Long
Public LootBuffer As String
'start declaring autoattack log
Public LastID
Public TargetID As Long
Public MaxEXP As Long
'stop declaring autoattack log
Public ChatTipi1 As Long
Public KO_RCVFNC As Long
Public KO_TITLE As String
Public KO_HANDLE As Long
Public KO_PID As Long
Public KO_PTR_CHR As Long
Public KO_PTR_CHR1 As Long
Public KO_PTR_DLG As Long
Public KO_PTR_PKT As Long
Public KO_SND_FNC As Long
Public KO_RECVHK As Long
Public KO_RCVHKB As Long
Public KO_ADR_CHR As Long
Public KO_ADR_DLG As Long
Public KO_OFF_RTM As Long
Public KO_OFF_NT As Long
Public KO_OFF_CLASS As Long
Public KO_OFF_SWIFT As Long
Public KO_OFF_HP As Long
Public KO_OFF_MAXHP As Long
Public KO_OFF_MP As Long
Public KO_OFF_MAXMP As Long
Public KO_OFF_MOB As Long
Public KO_OFF_WH As Long
Public KO_OFF_SIT As Long
Public KO_OFF_LUP As Long
Public KO_OFF_LUP2 As Long
Public KO_OFF_Y As Long
Public KO_OFF_ID As Long
Public KO_OFF_HD As Long
Public KO_OFF_X As Long
Public KO_OFF_SEL As Long
Public KO_OFF_LUPINE As Long
Public KO_OFF_EXP As Long
Public KO_OFF_MAXEXP As Long
Public KO_OFF_AP As Long
Public KO_OFF_GOLD As Long
Public nation As Long
Public KO_TITLE1 As String
Public DINPUT_Handle As Long
Public DINPUT_lpBaseOfDLL As Long
Public DINPUT_SizeOfImage As Long
Public DINPUT_EntryPoint As Long
Public DINPUT_KEYDMA As Long
Public DINPUT_K_1 As Long
Public DINPUT_K_2 As Long
Public DINPUT_K_3 As Long
Public DINPUT_K_4 As Long
Public DINPUT_K_5 As Long
Public DINPUT_K_6 As Long
Public DINPUT_K_7 As Long
Public DINPUT_K_8 As Long
Public DINPUT_K_Z As Long
Public DINPUT_K_C As Long
Public DINPUT_K_S As Long
Public DINPUT_K_R As Long
Public KO_CHR As Long
Public MP1 As Long
Public Type MODULEINFO
lpBaseOfDLL As Long
SizeOfImage As Long
EntryPoint As Long
End Type
' dll inject komutlari
Public Function HookDI8() As Boolean
Dim Ret As Long
Dim lmodinfo As MODULEINFO
DINPUT_Handle = 0
DINPUT_Handle = FindModuleHandle("dinput8.dll")
Ret = GetModuleInformation(KO_HANDLE, DINPUT_Handle, lmodinfo, Len(lmodinfo))
If Ret <> 0 Then
With lmodinfo
DINPUT_EntryPoint = .EntryPoint
DINPUT_lpBaseOfDLL = .lpBaseOfDLL
DINPUT_SizeOfImage = .SizeOfImage
End With
Else
Exit Function
End If
SetupDInput
HookDI8 = True
End Function
Public Function FindModuleHandle(ModuleName As String) As Long
Dim hModules(1 To 256) As Long
Dim BytesReturned As Long
Dim ModuleNumber As Byte
Dim TotalModules As Byte
Dim FileName As String * 128
Dim ModName As String
EnumProcessModules KO_HANDLE, hModules(1), 1024, BytesReturned
TotalModules = BytesReturned / 4
For ModuleNumber = 1 To TotalModules
GetModuleFileNameExA KO_HANDLE, hModules(ModuleNumber), FileName, 128
ModName = Left(FileName, InStr(FileName, Chr(0)) - 1)
If UCase(Right(ModName, Len(ModuleName))) = UCase(ModuleName) Then
FindModuleHandle = hModules(ModuleNumber)
End If
Next
End Function
Sub SetupDInput()
DINPUT_KEYDMA = FindDInputKeyPtr
If DINPUT_KEYDMA <> 0 Then
DINPUT_K_1 = DINPUT_KEYDMA + 2
DINPUT_K_2 = DINPUT_KEYDMA + 3
DINPUT_K_3 = DINPUT_KEYDMA + 4
DINPUT_K_4 = DINPUT_KEYDMA + 5
DINPUT_K_5 = DINPUT_KEYDMA + 6
DINPUT_K_6 = DINPUT_KEYDMA + 7
DINPUT_K_7 = DINPUT_KEYDMA + 8
DINPUT_K_8 = DINPUT_KEYDMA + 9
DINPUT_K_Z = DINPUT_KEYDMA + 44
DINPUT_K_C = DINPUT_KEYDMA + 46
DINPUT_K_S = DINPUT_KEYDMA + 31
DINPUT_K_R = DINPUT_KEYDMA + 19
End If
End Sub
Function FindDInputKeyPtr() As Long
Dim pBytes() As Byte
Dim pSize As Long
Dim X As Long
pSize = DINPUT_SizeOfImage
ReDim pBytes(1 To pSize)
ReadByteArray DINPUT_lpBaseOfDLL, pBytes, pSize
For X = 1 To pSize - 10
If pBytes(X) = &H57 And pBytes(X + 1) = &H6A And pBytes(X + 2) = &H40 And pBytes(X + 3) = &H33 And pBytes(X + 4) = &HC0 And pBytes(X + 5) = &H59 And pBytes(X + 6) = &HBF Then
FindDInputKeyPtr = Val("&H" & IIf(Len(Hex(pBytes(X + 10))) = 1, "0" & Hex(pBytes(X + 10)), Hex(pBytes(X + 10))) & IIf(Len(Hex(pBytes(X + 9))) = 1, "0" & Hex(pBytes(X + 9)), Hex(pBytes(X + 9))) & IIf(Len(Hex(pBytes(X + 8))) = 1, "0" & Hex(pBytes(X + 8)), Hex(pBytes(X + 8))) & IIf(Len(Hex(pBytes(X + 7))) = 1, "0" & Hex(pBytes(X + 7)), Hex(pBytes(X + 7))))
Exit For
End If
Next
End Function
' Buraya ben yolla yazdim sizde istediginizi yaza bilir siniz.
'ama prejedeki Bütün Yolla yazan yerleri degistirmelisiniz.
Function yolla(pKey As String) As Long
pKey = Strings.UCase(pKey)
Select Case pKey
Case "S"
yolla = DINPUT_K_S
Case "Z"
yolla = DINPUT_K_Z
Case "1"
yolla = DINPUT_K_1
Case "2"
yolla = DINPUT_K_2
Case "3"
yolla = DINPUT_K_3
Case "4"
yolla = DINPUT_K_4
Case "5"
yolla = DINPUT_K_5
Case "6"
yolla = DINPUT_K_6
Case "7"
yolla = DINPUT_K_7
Case "8"
yolla = DINPUT_K_8
Case "C"
yolla = DINPUT_K_C
Case "R"
yolla = DINPUT_K_R
End Select
End Function
Sub WriteByte(Addr As Long, pVal As Byte)
Dim pbw As Long
WriteProcessMem KO_HANDLE, Addr, pVal, 1, pbw
End Sub
Sub ReadByteArray(Addr As Long, pmem() As Byte, pSize As Long)
Dim Value As Byte
ReDim pmem(1 To pSize) As Byte
ReadProcessMem KO_HANDLE, Addr, pmem(1), pSize, 0&
End Sub
' Buraya ben TUS yazdim sizde istediginizi yaza bilir siniz.
'ama prejedeki Bütün TUS yazan yerleri degistirmelisiniz.
Sub Tus(pKey As Long, Optional pTimeMS As Long = 50)
WriteByte pKey, 128
f_Sleep pTimeMS, True
WriteByte pKey, 0
End Sub
Sub f_Sleep(pMS As Long, Optional pDoevents As Boolean = False)
Dim pTime As Long
pTime = GetTickCount
Do While pMS + pTime > GetTickCount
If pDoevents = True Then DoEvents
Loop
End Sub
Public Function ReadLong(Addr As Long) As Long 'read a 4 byte value
Dim Value As Long
ReadProcessMem KO_HANDLE, Addr, Value, 4, 0&
ReadLong = Value
End Function
Public Function ReadFloat(Addr As Long) As Long 'read a float value
Dim Value As Single
ReadProcessMem KO_HANDLE, Addr, Value, 4, 0&
ReadFloat = Value
End Function
Public Function WriteFloat(Addr As Long, Val As Single) 'write a float value
WriteProcessMem KO_HANDLE, Addr, Val, 4, 0&
End Function
Public Function WriteLong(Addr As Long, Val As Long) ' write a 4 byte value
WriteProcessMem KO_HANDLE, Addr, Val, 4, 0&
End Function
Public Function SetTopMostWindow(hwnd As Long, Topmost As Boolean) As Long
If Topmost = True Then 'Make the window topmost
SetTopMostWindow = SetWindowPos(hwnd, HWND_TOPMOST, 0, 0, 0, 0, FLAGS)
Else
SetTopMostWindow = SetWindowPos(hwnd, HWND_NOTOPMOST, 0, 0, 0, 0, FLAGS)
SetTopMostWindow = False
End If
End Function
Public Function ReadIni(FileName As String, Section As String, Key As String) As String
Dim RetVal As String * 255, v As Long
v = GetPrivateProfileString(Section, Key, "", RetVal, 255, FileName)
ReadIni = Left(RetVal, v)
End Function
'writes an Ini string
Public Function WriteIni(FileName As String, Section As String, Key As String, Value As String)
WritePrivateProfileString Section, Key, Value, FileName
End Function
Public Function ConvHEX2ByteArray(pStr As String, pByte() As Byte)
Dim i As Long
Dim j As Long
ReDim pByte(1 To Len(pStr) / 2)
j = LBound(pByte) - 1
For i = 1 To Len(pStr) Step 2
j = j + 1
pByte(j) = CByte("&H" & Mid(pStr, i, 2))
Next
End Function
Public Function WriteByteArray(pAddy As Long, pmem() As Byte, pSize As Long)
WriteProcessMem KO_HANDLE, pAddy, pmem(LBound(pmem)), pSize, 0&
End Function
'start packet handling
Function ExecuteRemoteCode(pCode() As Byte, Optional WaitExecution As Boolean = False) As Long
Dim FuncPtr As Long
Dim hThread As Long, ThreadID As Long, Ret As Long
Dim SE As SECURITY_ATTRIBUTES
SE.nLength = Len(SE)
SE.bInheritHandle = False
ExecuteRemoteCode = 0
FuncPtr = VirtualAllocEx(KO_HANDLE, 0, 1024, MEM_COMMIT, PAGE_READWRITE)
If FuncPtr <> 0 Then
WriteByteArray FuncPtr, pCode, UBound(pCode) - LBound(pCode) + 1
hThread = CreateRemoteThread(ByVal KO_HANDLE, SE, 0, ByVal FuncPtr, 0&, 0&, ThreadID)
If hThread Then
Ret = WaitForSingleObject(hThread, INFINITE)
ExecuteRemoteCode = ThreadID
End If
CloseHandle hThread
Ret = VirtualFreeEx(KO_HANDLE, FuncPtr, 0, MEM_RELEASE)
End If
End Function
Function SendPackets(pPacket() As Byte)
Dim BytesAddr As Long
Dim pSize As Long
Dim pCode() As Byte
'60 PUSHAD
'A1 84898100 MOV EAX,DWORD PTR DS:[818984]
'8B0D 84898100 MOV ECX,DWORD PTR DS:[818984]
'68 dword(packet size)
'68 dword(BytesAddr) 'call packetsize
'BF C0184500 MOV EDI,_KnightO.004518C0 -> entry address
'FFD7
'61
'C3
'KO_PTR_PKT = &H818984 'packet function
'KO_SND_FNC = &H451B80 'entry adress
pSize = UBound(pPacket) - LBound(pPacket) + 1
BytesAddr = VirtualAllocEx(KO_HANDLE, 0, 1024, MEM_COMMIT, PAGE_READWRITE)
If BytesAddr <> 0 Then
WriteByteArray BytesAddr, pPacket, pSize
ConvHEX2ByteArray "60A1" & AlignDWORD(KO_PTR_PKT) & "8B0D" & AlignDWORD(KO_PTR_PKT) & "68" & AlignDWORD(pSize) & "68" & AlignDWORD(BytesAddr) & "BF" & AlignDWORD(KO_SND_FNC) & "FFD761C3", pCode
ExecuteRemoteCode pCode, True
End If
VirtualFreeEx KO_HANDLE, BytesAddr, 0, MEM_RELEASE&
End Function
'

Function AlignDWORD(pParam As Long) As String
Dim HiW As Integer
Dim LoW As Integer
Dim HiBHiW As Byte
Dim HiBLoW As Byte
Dim LoBHiW As Byte
Dim LoBLoW As Byte
HiW = HiWord(pParam)
LoW = LoWord(pParam)
HiBHiW = HiByte(HiW)
HiBLoW = HiByte(LoW)
LoBHiW = LoByte(HiW)
LoBLoW = LoByte(LoW)
AlignDWORD = IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW))
End Function 'sansa bak 8 mis zate


Function AlignDWORD8(pParam As Long) As String
Dim HiW As Integer
Dim LoW As Integer
Dim HiBHiW As Byte
Dim HiBLoW As Byte
Dim LoBHiW As Byte
Dim LoBLoW As Byte
HiW = HiWord(pParam)
LoW = LoWord(pParam)
HiBHiW = HiByte(HiW)
HiBLoW = HiByte(LoW)
LoBHiW = LoByte(HiW)
LoBLoW = LoByte(LoW)
AlignDWORD8 = IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW)) & _
IIf(Len(Hex(LoBLoW)) = 1, "0" & Hex(LoBLoW), Hex(LoBLoW)) & _
IIf(Len(Hex(HiBLoW)) = 1, "0" & Hex(HiBLoW), Hex(HiBLoW)) & _
IIf(Len(Hex(LoBHiW)) = 1, "0" & Hex(LoBHiW), Hex(LoBHiW)) & _
IIf(Len(Hex(HiBHiW)) = 1, "0" & Hex(HiBHiW), Hex(HiBHiW))
End Function
Public Function HiByte(ByVal wParam As Integer) As Byte
HiByte = (wParam And &HFF00&) \ (&H100)
End Function
Public Function LoByte(ByVal wParam As Integer) As Byte
LoByte = wParam And &HFF&
End Function
Function LoWord(DWord As Long) As Integer
If DWord And &H8000& Then '
LoWord = DWord Or &HFFFF0000
Else
LoWord = DWord And &HFFFF&
End If
End Function
Function HiWord(DWord As Long) As Integer
HiWord = (DWord And &HFFFF0000) \ &H10000
End Function
Public Function LogFile(sStr As String)
Open CurDir & "\Log.txt" For Append As #1
Print #1, ";==> " & Time & " " & sStr & " ;<=="
Close #1
End Function
Public Function AttachKO() As Boolean
Dim inject As Boolean
If FindWindow(vbNullString, KO_TITLE) Then
MSName = "\\.\mailslot\ByS0x" & Hex(GetTickCount)
GetWindowThreadProcessId FindWindow(vbNullString, KO_TITLE), KO_PID
KO_HANDLE = OpenProcess(PROCESS_ALL_ACCESS, False, KO_PID)
If KO_HANDLE = 0 Then
MsgBox ("Cannot get handle from KO(" & KO_PID & ").")
AttachKO = False
End If
Hook = HookDI8 'HooKDI8 dinput8.dll degerini kontrol ettiriyoruz
If Hook = False Then 'eger hook false ise
AttachKO = False 've attachko muzu false ediyoruz.
MsgBox "Dinput8.dll Yüklenemiyor.Koxpun Bulundupu Klasöre Dinput8.dll atiniz.", vbDefaultButton2, "Dikkat"
End If
MSHandle = EstablishMailSlot(MSName) 'mail slotumuzu açiyoruz
If MSHandle = 0 Then End 'eger MSHandle esitse sifir a demekki mesaj gelmiyor Ko dan sonlandir diyoruz.
If KO_PID = 0 Then End 'Ko nun pid degeride 0 a esitse gene sonlandiriyoruz programimizi
'Evet iste burasi çok önemli mail slotu için ko nun exe sinde bazi degisiklik yapiyor
'MsgBox (KO_PID)
'prevent iexplore to be launched on exit
'Dim pBytess() As Byte
'00670A23 E9 09010000 JMP KnightOn.00670B31
'00670A28 90 NOP
'ConvHEX2ByteArray "E90901000090", pBytess ' patch hackshield
'WriteByteArray &H670A23, pBytess, UBound(pBytess) - LBound(pBytess) + 1
AttachKO = True
Else
MsgBox "Ilk Önce Oyunu Acin", vbDefaultButton1, "Dikkat"
End If
End Function
Public Function EstablishMailSlot(ByVal MailSlotName As String, Optional MaxMessageSize As Long = 0, Optional ReadTimeOut As Long = 50) As Long
EstablishMailSlot = CreateMailslot(MailSlotName, MaxMessageSize, ReadTimeOut, ByVal 0&)
End Function
Function LoadOffsets()
KO_TITLE = Form1.Text1.Text
KO_PTR_CHR = &HB6E3BC
KO_PTR_DLG = &HB6FC94
KO_PTR_PKT = &HB6FC60 'packet function
KO_SND_FNC = &H473870 'entry adress
'KO_RECVHK = &HB6EC74 '5C5193
'KO_RCVHKB = &H5C519A '5C519A
KO_OFF_SWIFT = 1582
KO_OFF_CLASS = 1416
KO_OFF_NT = 1412
KO_OFF_HP = 1428
KO_OFF_MAXHP = 1424
KO_OFF_MP = 2364
KO_OFF_MAXMP = 2360
KO_OFF_SIT = 2790
KO_OFF_MOB = 1332
KO_OFF_WH = 1432
KO_OFF_Y = 184
KO_OFF_X = 176
KO_OFF_LUP = 3204
KO_OFF_LUP2 = 2800
KO_OFF_EXP = 2072
KO_OFF_MAXEXP = 2068
KO_OFF_AP = 2136
KO_OFF_GOLD = 2064
KO_OFF_ID = 1383
KO_OFF_HD = 1300
nation = &H584
ko = ReadLong(KO_PTR_CHR)
End Function
Sub Skill(skillid As String)
Dim ID As String
Dim ID1 As String
Dim ID2 As String
Dim IDs As Long
Dim skillid1
Dim skillid2
Dim skillid3
Dim skillhex As String
Dim skillid4 As String
skillhex = Hex(skillid)
skillid1 = Mid$(skillhex, 4, 6)
skillid2 = Mid$(skillhex, 2, 2)
skillid3 = Mid$(skillhex, 1, 1)
IDs = ReadLong(KO_ADR_CHR + KO_OFF_ID)
ID = AlignDWORD(IDs)
ID1 = Strings.Mid(ID, 3, 2)
ID2 = Strings.Mid(ID, 5, 2)
Dim pBytes(1 To 18) As Byte
pBytes(1) = &H31
pBytes(2) = &H3
pBytes(3) = "&H" & skillid1
pBytes(4) = "&H" & skillid2
pBytes(5) = "&H" & skillid3
pBytes(6) = &H0
pBytes(7) = "&H" & ID1
pBytes(8) = "&H" & ID2
pBytes(9) = "&H" & ID1
pBytes(10) = "&H" & ID2
pBytes(11) = &H0
pBytes(12) = &H0
pBytes(13) = &H0
pBytes(14) = &H0
pBytes(15) = &H0
pBytes(16) = &H0
pBytes(17) = &H0
pBytes(18) = &H0
SendPackets pBytes
PotionTimer = Now
End Sub
Private Function ReadMessage(MailMessage As String, MessagesLeft As Long)
Dim lBytesRead As Long
Dim lNextMsgSize As Long
Dim lpBuffer As String
ReadMessage = False
Call GetMailslotInfo(MSHandle, ByVal 0&, lNextMsgSize, MessagesLeft, ByVal 0&)
If MessagesLeft > 0 And lNextMsgSize <> MAILSLOT_NO_MESSAGE Then
lBytesRead = 0
lpBuffer = String$(lNextMsgSize, Chr$(0))
Call ReadFile(MSHandle, ByVal lpBuffer, Len(lpBuffer), lBytesRead, ByVal 0&)
If lBytesRead <> 0 Then
MailMessage = Left(lpBuffer, lBytesRead)
ReadMessage = True
Call GetMailslotInfo(MSHandle, ByVal 0&, lNextMsgSize, MessagesLeft, ByVal 0&)
End If
End If
End Function
Private Function CheckForMessages(MessageCount As Long)
Dim lMsgCount As Long
Dim lNextMsgSize As Long
CheckForMessages = False
GetMailslotInfo MSHandle, ByVal 0&, lNextMsgSize, lMsgCount, ByVal 0&
MessageCount = lMsgCount
CheckForMessages = True
End Function
Private Function HexString(EvalString As String) As String
Dim intStrLen As Integer
Dim intLoop As Integer
Dim strHex As String
EvalString = Trim(EvalString)
intStrLen = Len(EvalString)
For intLoop = 1 To intStrLen
strHex = strHex & Hex(Asc(Mid(EvalString, intLoop, 1)))
Next
hexword = strHex
End Function
Function Notice(NoticeYazi As String)
Dim pStr As String
Dim pBytes() As Byte
HexString NoticeYazi
If Form1.Combo3.ListIndex = 0 Then
pStr = "10" + "01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 1 Then
pStr = "10" + "05" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 2 Then
pStr = "11" + "03" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 3 Then
pStr = "11" + "06" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 4 Then
pStr = "11" + "0E" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
Else
If Form1.Combo3.ListIndex = 1 Then
pStr = "11" + "0F" + "FF01" + hexword
ConvHEX2ByteArray pStr, pBytes
SendPackets pBytes
End If
End If
End If
End If
End If
End If
End Function
Modül ile kullanılabilinecek fonksiyonlar :
GM'leri görme (denenmedi)
Oto Lup
Oto Kutu
Tarot Hack +1 HP
Süper Okçu Yapmak
Stat Sıfırlama
Start Butonu
Skill Sıfırlama
Sınırsız Swift
Seri CS
Ölünce Pc Kapat
Ölünce Oyunu Kapat
Oto TS
Oto Rpr
Oto Party
Oto Hp-Mp Çektirme
Irk Hack
Hazzard
Oto Ft Giriş
Hp Düşerse Town at
Char Sabitlemek
Char Gizlemek
Atak Başlat
Wall Hack
Koxpu Oyuna Bağlamak
Alt-Tab Ekle
KnightOnline.exe Yolu Göstermek