domingo, 18 de enero de 2009

Códigos anti debug para VB6


Pues eso aca dejo algunos codigos antidebugging que se usar para mis aplicaciones:

Para VB6:

Debug.Print 1 / 0

Esta sentencia genera una exepción de división por cero cuando la aplicación es debugueda.

____________________________________________________________________________


Public Declare Function IsDebuggerPresent Lib "kernel32" () As Long
Private Sub Form_Load()
If IsDebuggerPresent Then
........
End Sub

Ejemplo de como detectar un debugger con la rutina de kernel32, IssDebuggerPresent

____________________________________________________________________________

Public Declare Function OutputDebugStringA Lib "kernel32" (ByVal lpString As String) As Long

Private Sub Form_Load()
Dim AA As String
Dim i As Integer

For i = 1 To 200
AA = AA & "%s"
Next i

MsgBox OutputDebugStringA(AA)
End Sub

Este code genera una exepción de desbordamiento de pila en algunos debuggers, mas específicamente el olly 1.10.Lo hace entrar en Deadlock
____________________________________________________________________________


'---------------------------------------------------------------------------------------
' Module : mGetProcAddress
' DateTime : 06/10/2008 20:06
' Author : Cobein
' Mail : cobein27@hotmail.com
' WebPage : http://www.advancevb.com.ar
' Member of : http://hackhound.org/
' Purpose : GetProcAddress alternative function
' Usage : At your own risk
' Requirements: None
' Distribution: You can freely use this code in your own
' applications, but you may not reproduce
' or publish this code on any web site,
' online service, or distribute as source
' on any media without express permission.
'
' Reference : Based on ExtremeCoder sample [http://www.rohitab.com/discuss/lofiversion/index.php/t30773.html]
'
' History : 06/10/2008 First Cut....................................................
' 06/10/2008 Minor change in buffer size to increase speed................
'---------------------------------------------------------------------------------------
Option Explicit

Private Declare Function LoadLibraryA Lib "kernel32" (ByVal lpLibFileName As String) As Long
Private Declare Sub GetMem4 Lib "msvbvm60" (ByVal Addr As Long, RetVal As Long)
Private Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As String) As Long
Private Declare Function SysAllocString Lib "oleaut32.dll" (ByVal pOlechar As Long) As String

Public Function GetProcAddressAlt(ByVal sLib As String, ByVal sMod As String) As Long
Dim lLib As Long
Dim i As Long

lLib = LoadLibraryA(sLib)

If Not lLib = 0 Then
Dim dwNumberOfNames As Long
Dim dwNamesOffset As Long
Dim dwNameRVAs As Long
Dim dwFuncOffset As Long
Dim dwFuncRVAs As Long

GetMem4 (lLib + &H3C), i
GetMem4 (lLib + i + &H78), i

GetMem4 (lLib + i + &H18), dwNumberOfNames
GetMem4 (lLib + i + &H20), dwNamesOffset
GetMem4 (lLib + i + &H1C), dwFuncOffset

Dim sBuff As String * 128
Dim sName As String

For i = 0 To dwNumberOfNames - 1
GetMem4 (lLib + dwNamesOffset + i * &H4), dwNameRVAs
GetMem4 (lLib + dwFuncOffset + i * &H4), dwFuncRVAs

sBuff = SysAllocString(lLib + dwNameRVAs)
sName = Left$(sBuff, lstrlen(sBuff))

If sName = sMod Then
GetProcAddressAlt = lLib + dwFuncRVAs
Exit Function
End If
Next
End If

End Function

Este modulo sirve para buscar nombre de procesos tales como: ollydbg, snd, etc.
Con el pueden saber si se ha cargado X programa, se puede mejorar el modulo para que detecte si la cadena ingresada se encuentra en una porción del modulo con el cual esta siendo comprobada, en ese caso detectaria algunas variantes de olly, ya que la mayoria agregan por ejemplo: Yoda's - olldbg. Entonces si comparamos con olly nos daría que son distintas pero si lo hacemos como si fuera un Like, o sea q sea igual o este contenida nos devolvería ese proceso sospechoso tbn.


____________________________________________________________________________
Private Declare Function OutputDebugStringA Lib "kernel32" (ByVal lpString As String) As Long

Private Sub Form_Load()
If IsDebuggerActive Then
MsgBox "Debugger Present"
End If
End Sub

Private Function IsDebuggerActive() As Boolean
IsDebuggerActive = Not (OutputDebugStringA("=)") = 1)
End Function

Otro ejemplo con OutputDebugStringA pero en este caso genera una exepción.

____________________________________________________________________________

Option Explicit

Private Declare Function CheckRemoteDebuggerPresent Lib "kernel32.dll" (ByVal hProcess As Long, fResult As Long) As Long

Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function GetCurrentProcessId Lib "kernel32" () As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long

Private Const PROCESS_ALL_ACCESS As Long = &H1F0FFF


Private Sub Form_Load()

Dim fResult As Long
Dim hProcess As Long

hProcess = OpenProcess(ByVal PROCESS_ALL_ACCESS, ByVal 0&, ByVal GetCurrentProcessId)
Call CheckRemoteDebuggerPresent(hProcess, fResult)
CloseHandle hProcess
.........

End Sub


En este caso testeamos remotamente q nuestro programa no sea debuggeado, si es debuggeado fResult nos dara 1 como valor.
____________________________________________________________________________

'IsDbgCrss
Private Declare Function CsrGetProcessId Lib "ntdll.dll" () As Long
Private Declare Function OpenProcess Lib "kernel32.dll" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long

'---------------------------------------------------------------------------------------
' Procedure : IsDbgCsrss
' Author : Karcrack
' Date : 30/12/2008
' Purpose : Check if our app is being debugged
' Usage : If IsDbgCrss = True Then MsgBox "I'm Debugged"
' Tested On : OllyDbg v2.0 ß
' Reference : http://www.piotrbania.com/all/articles/antid.txt
'---------------------------------------------------------------------------------------
'
Public Function IsDbgCsrss() As Boolean
IsDbgCsrss = CBool(OpenProcess(&H1F0FFF, 0, CsrGetProcessId)) '&H1F0FFF = PROCESS_ALL_ACCESS
End Function

Este codigo detecta si se esta debugueando nuestra aplicación.
____________________________________________________________________________


Option Explicit

Private Const ANYSIZE_ARRAY = 1
Private Const TOKEN_ADJUST_PRIVILEGES = &H20
Private Const TOKEN_QUERY = &H8
Private Const SE_PRIVILEGE_ENABLED = &H2

Private Type LUID
LowPart As Long
HighPart As Long
End Type
Private Type LUID_AND_ATTRIBUTES
pLuid As LUID
Attributes As Long
End Type
Private Type TOKEN_PRIVILEGES
PrivilegeCount As Long
Privileges(ANYSIZE_ARRAY) As LUID_AND_ATTRIBUTES
End Type


Private Declare Function AdjustTokenPrivileges Lib "advapi32.dll" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long
Private Declare Function LookupPrivilegeValue Lib "advapi32" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLUID As LUID) As Long
Private Declare Function GetCurrentProcess Lib "kernel32" () As Long
Private Declare Function OpenProcessToken Lib "advapi32.dll" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long



Public Const SE_DEBUG_NAME As String = "SeDebugPrivilege"


Public Declare Function RtlSetProcessIsCritical Lib "ntdll.dll" (ByVal NewValue As Boolean, ByVal OldValue As Boolean, ByVal WinLogon As Boolean)

Public Function ObtenerPrivilegios(ByVal privilegio As String) As Long

Dim lpLUID As LUID
Dim lpToken As TOKEN_PRIVILEGES
Dim lpAntToken As TOKEN_PRIVILEGES
Dim hToken As Long
Dim hProcess As Long
Dim res As Long

hProcess = GetCurrentProcess()
res = OpenProcessToken(hProcess, TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, hToken)
If res = 0 Then
Exit Function
End If
res = LookupPrivilegeValue(vbNullString, privilegio, lpLUID)
If res = 0 Then
Exit Function
End If
With lpToken
.PrivilegeCount = 1
.Privileges(0).Attributes = SE_PRIVILEGE_ENABLED
.Privileges(0).pLuid = lpLUID
End With

res = AdjustTokenPrivileges(hToken, False, lpToken, Len(lpToken), lpAntToken, Len(lpAntToken))
If res = 0 Then
Exit Function
End If
ObtenerPrivilegios = res
End Function






'*************************************************************************
'*************************************************************************
' Uso de RtlSetProcessIsCritical para setear nuestro proceso, como proceso
' critico del sistema: del mismo modo que csrss.exe o winlogon
' XcryptOR - Made In Colombia
'**************************************************************************
'*************************************************************************
Private Sub Form_Load()
On Error Resume Next
ObtenerPrivilegios SE_DEBUG_NAME ' obtiene privilegios de Debugeo
Call RtlSetProcessIsCritical(0, 0, 1) ' setea nuestro proceso como Proceso Critico
End Sub




Bueno como dice el comentario para setear a nuestra aplicación privilegios.

____________________________________________________________________________



Y por ultimo algunos trucos para dificultar un poco mas:



App.TaskVisible = False

App.Title = ""



Saludos

No hay comentarios: