elhacker.net cabecera Bienvenido(a), Visitante. Por favor Ingresar o Registrarse
¿Perdiste tu email de activación?.

 

 


Tema destacado: Introducción a la Factorización De Semiprimos (RSA)


+  Foro de elhacker.net
|-+  Programación
| |-+  Programación General
| | |-+  .NET (C#, VB.NET, ASP)
| | | |-+  Programación Visual Basic (Moderadores: LeandroA, seba123neo)
| | | | |-+  modulo clss md5
0 Usuarios y 1 Visitante están viendo este tema.
Páginas: [1] Ir Abajo Respuesta Imprimir
Autor Tema: modulo clss md5  (Leído 2,507 veces)
rembolso

Desconectado Desconectado

Mensajes: 163



Ver Perfil
modulo clss md5
« en: 17 Abril 2010, 08:07 am »

hola .  ando buscando un modulo  para descifrar md5 . lo intente hacer revirtiendo el proceso de cifrado . pero me dio cualquier cosa jajaj , si alguno lo tiene me lo podría pasar   :-X


« Última modificación: 17 Abril 2010, 17:06 pm por rembolso » En línea

Shell Root
Moderador Global
***
Desconectado Desconectado

Mensajes: 3.723


<3


Ver Perfil WWW
Re: modulo clss md5
« Respuesta #1 en: 17 Abril 2010, 08:14 am »



« Última modificación: 17 Abril 2010, 08:17 am por Alex@ShellRoot » En línea

Por eso no duermo, por si tras mi ventana hay un cuervo. Cuelgo de hilos sueltos sabiendo que hay veneno en el aire.
Elemental Code


Desconectado Desconectado

Mensajes: 622


Im beyond the system


Ver Perfil
Re: modulo clss md5
« Respuesta #2 en: 17 Abril 2010, 15:53 pm »

ni idea como se hace  :huh: soy medio nuevo pero entendi lo que queres hacer aver si alguien te da una mano.

Con un codigo obtenes el MD5 de una frase o palabra o texto.

y queres que despues con el MD5 que habias sacado recuperes la palabra¿

es asi?
En línea

I CODE FOR $$$
Programo por $$$
Hago tareas, trabajos para la facultad, lo que sea en VB6.0

Mis programas
rembolso

Desconectado Desconectado

Mensajes: 163



Ver Perfil
Re: modulo clss md5
« Respuesta #3 en: 17 Abril 2010, 17:05 pm »

Citar
Publicado por: Elemental Code
Insertar Cita
ni idea como se hace  :huh: soy medio nuevo pero entendi lo que queres hacer aver si alguien te da una mano.

Con un codigo obtenes el MD5 de una frase o palabra o texto.

y queres que despues con el MD5 que habias sacado recuperes la palabra¿

es asi?

si . eso es lo q quiero
En línea

Shell Root
Moderador Global
***
Desconectado Desconectado

Mensajes: 3.723


<3


Ver Perfil WWW
Re: modulo clss md5
« Respuesta #4 en: 17 Abril 2010, 17:09 pm »

Pues, o estoy muy desactualizado o no sé, pero creo que hasta el momento el hash MD5, no tiene algoritmo de desencryptación. Algunos lugares existen unos diccionarios de palabra en MD5.
En línea

Por eso no duermo, por si tras mi ventana hay un cuervo. Cuelgo de hilos sueltos sabiendo que hay veneno en el aire.
MCKSys Argentina
Moderador Global
***
Desconectado Desconectado

Mensajes: 5.465


Diviértete crackeando, que para eso estamos!


Ver Perfil
Re: modulo clss md5
« Respuesta #5 en: 18 Abril 2010, 17:15 pm »

Quizás esto te ayude:
Código:
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "MD5"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit

'  CLASE: MD5
'
'  DESCRIPCION:
'     Esta es una clase que encapsula un grupo de funciones del Algoritmo MD5.
'     El MD5 produce firmas digitales de 128 bits para bases de datos de cualquier largo.
'     Detalles en el RFC 1321. Esta implementación está derivada de la implementacion del
'     algoritmo MD5 de la RSA Data Security, Inc. (originalmente en C)
'
'  AUTOR:
'     Robert M. Hubley 12/1999
'     Modificado y traducido por MCKSys Argentina 2009
'
'
'=
'= Constantes de clase
'=
Private Const OFFSET_4 = 4294967296#
Private Const MAXINT_4 = 2147483647

Private Const S11 = 7
Private Const S12 = 12
Private Const S13 = 17
Private Const S14 = 22
Private Const S21 = 5
Private Const S22 = 9
Private Const S23 = 14
Private Const S24 = 20
Private Const S31 = 4
Private Const S32 = 11
Private Const S33 = 16
Private Const S34 = 23
Private Const S41 = 6
Private Const S42 = 10
Private Const S43 = 15
Private Const S44 = 21


'=
'= Variables de clase
'=
Private Estado(4) As Long
Private CuentaBytes As Long
Private BufferDeBytes(63) As Byte


'=
'= Propiedades de la clase
'=
Property Get RegisterA() As String
    RegisterA = Estado(1)
End Property

Property Get RegisterB() As String
    RegisterB = Estado(2)
End Property

Property Get RegisterC() As String
    RegisterC = Estado(3)
End Property

Property Get RegisterD() As String
    RegisterD = Estado(4)
End Property


'=
'= Funciones de clase
'=

'
' haya MD5 de matriz de bytes en una cadena Hexadecimal
'
Public Function DigestArrayToHexStr(Matriz() As Byte) As String
    MD5Init
    MD5Update UBound(Matriz) + 1, Matriz
    MD5Final
    DigestArrayToHexStr = GetValues
End Function

'
' Concatenar los 4 valores de Estado en un solso string
'
Public Function GetValues() As String
    GetValues = LongToString(Estado(1)) & LongToString(Estado(2)) & LongToString(Estado(3)) & LongToString(Estado(4))
End Function

'
' Convertir Long a cadena Hex
'
Private Function LongToString(Num As Long) As String
        Dim a As Byte
        Dim b As Byte
        Dim c As Byte
        Dim d As Byte
       
        a = Num And &HFF&
        If a < 16 Then
            LongToString = "0" & Hex(a)
        Else
            LongToString = Hex(a)
        End If
               
        b = (Num And &HFF00&) \ 256
        If b < 16 Then
            LongToString = LongToString & "0" & Hex(b)
        Else
            LongToString = LongToString & Hex(b)
        End If
       
        c = (Num And &HFF0000) \ 65536
        If c < 16 Then
            LongToString = LongToString & "0" & Hex(c)
        Else
            LongToString = LongToString & Hex(c)
        End If
       
        If Num < 0 Then
            d = ((Num And &H7F000000) \ 16777216) Or &H80&
        Else
            d = (Num And &HFF000000) \ 16777216
        End If
       
        If d < 16 Then
            LongToString = LongToString & "0" & Hex(d)
        Else
            LongToString = LongToString & Hex(d)
        End If
   
End Function

'
' Inicializar la clase
'   Esto debe llamarse antes de realizar cualquier cálculo
'
Public Sub MD5Init()
    CuentaBytes = 0
    Estado(1) = UnsignedToLong(1732584193#)
    Estado(2) = UnsignedToLong(4023233417#)
    Estado(3) = UnsignedToLong(2562383102#)
    Estado(4) = UnsignedToLong(271733878#)
End Sub

'
' MD5 Final
'
Public Sub MD5Final()
    Dim dblBits As Double
   
    Dim padding(72) As Byte
    Dim lngBytesBuffered As Long
   
    padding(0) = &H80
   
    dblBits = CuentaBytes * 8
   
    ' rellenar
    lngBytesBuffered = CuentaBytes Mod 64
    If lngBytesBuffered <= 56 Then
        MD5Update 56 - lngBytesBuffered, padding
    Else
        MD5Update 120 - CuentaBytes, padding
    End If
   
   
    padding(0) = UnsignedToLong(dblBits) And &HFF&
    padding(1) = UnsignedToLong(dblBits) \ 256 And &HFF&
    padding(2) = UnsignedToLong(dblBits) \ 65536 And &HFF&
    padding(3) = UnsignedToLong(dblBits) \ 16777216 And &HFF&
    padding(4) = 0
    padding(5) = 0
    padding(6) = 0
    padding(7) = 0
   
    MD5Update 8, padding
End Sub

'
' Partir datos de entrada en pedazos de 64 bytes
'
Public Sub MD5Update(InputLen As Long, InputBuffer() As Byte)
    Dim II As Integer
    Dim i As Integer
    Dim j As Integer
    Dim K As Integer
    Dim lngBufferedBytes As Long
    Dim lngBufferRemaining As Long
    Dim lngRem As Long
   
    lngBufferedBytes = CuentaBytes Mod 64
    lngBufferRemaining = 64 - lngBufferedBytes
    CuentaBytes = CuentaBytes + InputLen
    ' usar primero los resultados viejos del buffer
    If InputLen >= lngBufferRemaining Then
        For II = 0 To lngBufferRemaining - 1
            BufferDeBytes(lngBufferedBytes + II) = InputBuffer(II)
        Next II
        MD5Transform BufferDeBytes
       
        lngRem = (InputLen) Mod 64
        ' El transformador es multiplo de 64 asi que hagamos algunas transformaciones
        For i = lngBufferRemaining To InputLen - II - lngRem Step 64
            For j = 0 To 63
                BufferDeBytes(j) = InputBuffer(i + j)
            Next j
            MD5Transform BufferDeBytes
        Next i
        lngBufferedBytes = 0
    Else
      i = 0
    End If
   
    ' Buffear datos restantes
    For K = 0 To InputLen - i - 1
        BufferDeBytes(lngBufferedBytes + K) = InputBuffer(i + K)
    Next K
   
End Sub

'
' MD5 Transform
'
Private Sub MD5Transform(Buffer() As Byte)
    Dim x(16) As Long
    Dim a As Long
    Dim b As Long
    Dim c As Long
    Dim d As Long
   
    a = Estado(1)
    b = Estado(2)
    c = Estado(3)
    d = Estado(4)
   
    Decode 64, x, Buffer

    ' Pasada 1
    FF a, b, c, d, x(0), S11, -680876936
    FF d, a, b, c, x(1), S12, -389564586
    FF c, d, a, b, x(2), S13, 606105819
    FF b, c, d, a, x(3), S14, -1044525330
    FF a, b, c, d, x(4), S11, -176418897
    FF d, a, b, c, x(5), S12, 1200080426
    FF c, d, a, b, x(6), S13, -1473231341
    FF b, c, d, a, x(7), S14, -45705983
    FF a, b, c, d, x(8), S11, 1770035416
    FF d, a, b, c, x(9), S12, -1958414417
    FF c, d, a, b, x(10), S13, -42063
    FF b, c, d, a, x(11), S14, -1990404162
    FF a, b, c, d, x(12), S11, 1804603682
    FF d, a, b, c, x(13), S12, -40341101
    FF c, d, a, b, x(14), S13, -1502002290
    FF b, c, d, a, x(15), S14, 1236535329
   
    ' Pasada 2
    GG a, b, c, d, x(1), S21, -165796510
    GG d, a, b, c, x(6), S22, -1069501632
    GG c, d, a, b, x(11), S23, 643717713
    GG b, c, d, a, x(0), S24, -373897302
    GG a, b, c, d, x(5), S21, -701558691
    GG d, a, b, c, x(10), S22, 38016083
    GG c, d, a, b, x(15), S23, -660478335
    GG b, c, d, a, x(4), S24, -405537848
    GG a, b, c, d, x(9), S21, 568446438
    GG d, a, b, c, x(14), S22, -1019803690
    GG c, d, a, b, x(3), S23, -187363961
    GG b, c, d, a, x(8), S24, 1163531501
    GG a, b, c, d, x(13), S21, -1444681467
    GG d, a, b, c, x(2), S22, -51403784
    GG c, d, a, b, x(7), S23, 1735328473
    GG b, c, d, a, x(12), S24, -1926607734
   
    ' Pasada 3
    HH a, b, c, d, x(5), S31, -378558
    HH d, a, b, c, x(8), S32, -2022574463
    HH c, d, a, b, x(11), S33, 1839030562
    HH b, c, d, a, x(14), S34, -35309556
    HH a, b, c, d, x(1), S31, -1530992060
    HH d, a, b, c, x(4), S32, 1272893353
    HH c, d, a, b, x(7), S33, -155497632
    HH b, c, d, a, x(10), S34, -1094730640
    HH a, b, c, d, x(13), S31, 681279174
    HH d, a, b, c, x(0), S32, -358537222
    HH c, d, a, b, x(3), S33, -722521979
    HH b, c, d, a, x(6), S34, 76029189
    HH a, b, c, d, x(9), S31, -640364487
    HH d, a, b, c, x(12), S32, -421815835
    HH c, d, a, b, x(15), S33, 530742520
    HH b, c, d, a, x(2), S34, -995338651
   
    ' Pasada 4
    II a, b, c, d, x(0), S41, -198630844
    II d, a, b, c, x(7), S42, 1126891415
    II c, d, a, b, x(14), S43, -1416354905
    II b, c, d, a, x(5), S44, -57434055
    II a, b, c, d, x(12), S41, 1700485571
    II d, a, b, c, x(3), S42, -1894986606
    II c, d, a, b, x(10), S43, -1051523
    II b, c, d, a, x(1), S44, -2054922799
    II a, b, c, d, x(8), S41, 1873313359
    II d, a, b, c, x(15), S42, -30611744
    II c, d, a, b, x(6), S43, -1560198380
    II b, c, d, a, x(13), S44, 1309151649
    II a, b, c, d, x(4), S41, -145523070
    II d, a, b, c, x(11), S42, -1120210379
    II c, d, a, b, x(2), S43, 718787259
    II b, c, d, a, x(9), S44, -343485551
   
   
    Estado(1) = LongOverflowAdd(Estado(1), a)
    Estado(2) = LongOverflowAdd(Estado(2), b)
    Estado(3) = LongOverflowAdd(Estado(3), c)
    Estado(4) = LongOverflowAdd(Estado(4), d)

   
End Sub

Private Sub Decode(Length As Integer, OutputBuffer() As Long, InputBuffer() As Byte)
    Dim intDblIndex As Integer
    Dim intByteIndex As Integer
    Dim dblSum As Double
   
    intDblIndex = 0
    For intByteIndex = 0 To Length - 1 Step 4
        dblSum = InputBuffer(intByteIndex) + _
                                    InputBuffer(intByteIndex + 1) * 256# + _
                                    InputBuffer(intByteIndex + 2) * 65536# + _
                                    InputBuffer(intByteIndex + 3) * 16777216#
        OutputBuffer(intDblIndex) = UnsignedToLong(dblSum)
        intDblIndex = intDblIndex + 1
    Next intByteIndex
End Sub

'
' FF, GG, HH, y II para las transformaciones de la Pasada 1, 2, 3 y 4.
' La rotación es separada de la suma para prevenir recálculos
'
Private Function FF(a As Long, _
                    b As Long, _
                    c As Long, _
                    d As Long, _
                    x As Long, _
                    s As Long, _
                    ac As Long) As Long
    a = LongOverflowAdd4(a, (b And c) Or (Not (b) And d), x, ac)
    a = LongLeftRotate(a, s)
    a = LongOverflowAdd(a, b)
End Function

Private Function GG(a As Long, _
                    b As Long, _
                    c As Long, _
                    d As Long, _
                    x As Long, _
                    s As Long, _
                    ac As Long) As Long
    a = LongOverflowAdd4(a, (b And d) Or (c And Not (d)), x, ac)
    a = LongLeftRotate(a, s)
    a = LongOverflowAdd(a, b)
End Function

Private Function HH(a As Long, _
                    b As Long, _
                    c As Long, _
                    d As Long, _
                    x As Long, _
                    s As Long, _
                    ac As Long) As Long
    a = LongOverflowAdd4(a, b Xor c Xor d, x, ac)
    a = LongLeftRotate(a, s)
    a = LongOverflowAdd(a, b)
End Function

Private Function II(a As Long, _
                    b As Long, _
                    c As Long, _
                    d As Long, _
                    x As Long, _
                    s As Long, _
                    ac As Long) As Long
    a = LongOverflowAdd4(a, c Xor (b Or Not (d)), x, ac)
    a = LongLeftRotate(a, s)
    a = LongOverflowAdd(a, b)
End Function

'
' Rotar un long a la derecha
'
Function LongLeftRotate(value As Long, bits As Long) As Long
    Dim lngSign As Long
    Dim lngI As Long
    bits = bits Mod 32
    If bits = 0 Then LongLeftRotate = value: Exit Function
    For lngI = 1 To bits
        lngSign = value And &HC0000000
        value = (value And &H3FFFFFFF) * 2
        value = value Or ((lngSign < 0) And 1) Or (CBool(lngSign And _
                &H40000000) And &H80000000)
    Next
    LongLeftRotate = value
End Function

'
' Función para sumar 2 numeros sin signo como en C.
' los desbordamientos se ignoran!
'
Private Function LongOverflowAdd(Val1 As Long, Val2 As Long) As Long
    Dim lngHighWord As Long
    Dim lngLowWord As Long
    Dim lngOverflow As Long

    lngLowWord = (Val1 And &HFFFF&) + (Val2 And &HFFFF&)
    lngOverflow = lngLowWord \ 65536
    lngHighWord = (((Val1 And &HFFFF0000) \ 65536) + ((Val2 And &HFFFF0000) \ 65536) + lngOverflow) And &HFFFF&
    LongOverflowAdd = UnsignedToLong((lngHighWord * 65536#) + (lngLowWord And &HFFFF&))
End Function

'
' Función para sumar 2 numeros sin signo como en C.
' los desbordamientos se ignoran!
'
Private Function LongOverflowAdd4(Val1 As Long, Val2 As Long, val3 As Long, val4 As Long) As Long
    Dim lngHighWord As Long
    Dim lngLowWord As Long
    Dim lngOverflow As Long

    lngLowWord = (Val1 And &HFFFF&) + (Val2 And &HFFFF&) + (val3 And &HFFFF&) + (val4 And &HFFFF&)
    lngOverflow = lngLowWord \ 65536
    lngHighWord = (((Val1 And &HFFFF0000) \ 65536) + _
                   ((Val2 And &HFFFF0000) \ 65536) + _
                   ((val3 And &HFFFF0000) \ 65536) + _
                   ((val4 And &HFFFF0000) \ 65536) + _
                   lngOverflow) And &HFFFF&
    LongOverflowAdd4 = UnsignedToLong((lngHighWord * 65536#) + (lngLowWord And &HFFFF&))
End Function

'
' Convertir un double sin signo en un long
'
Private Function UnsignedToLong(value As Double) As Long
        If value < 0 Or value >= OFFSET_4 Then Error 6 ' Desbordamiento
        If value <= MAXINT_4 Then
          UnsignedToLong = value
        Else
          UnsignedToLong = value - OFFSET_4
        End If
      End Function

'
' Convertir un long en un Double sin signo
'
Private Function LongToUnsigned(value As Long) As Double
        If value < 0 Then
          LongToUnsigned = value + OFFSET_4
        Else
          LongToUnsigned = value
        End If
End Function

Saludos!
En línea

MCKSys Argentina

"Si piensas que algo está bien sólo porque todo el mundo lo cree, no estás pensando."

seba123neo
Moderador
***
Desconectado Desconectado

Mensajes: 3.621



Ver Perfil WWW
Re: modulo clss md5
« Respuesta #6 en: 18 Abril 2010, 17:22 pm »

busca en PSC esta lleno...
En línea

Páginas: [1] Ir Arriba Respuesta Imprimir 

Ir a:  
WAP2 - Aviso Legal - Powered by SMF 1.1.21 | SMF © 2006-2008, Simple Machines