Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

MD5 Hash

christian_rackl
Beginner
3,398 Views
Has anybody got a function for the calculation of a MD5 Checksum of a string for fortran??
0 Kudos
11 Replies
keefer
Beginner
3,398 Views
No. We don't even know what you are talking about. Try "Numerical Recipies" (Press, et al.) to see if they do.
Regards,
Keith
0 Kudos
christian_rackl
Beginner
3,398 Views
MD5 is a well known cryptography algorithm
(similar to CRC32, AES or SHA-2)
I need this because i need to create a license manager for my program.
The benefit of a MD5 Checksum is that it is not reversible. So it can only be cracked by a brute force attack which tries all possible combinations.
I found a sample source in C but i'm not sure if i can manage to translate it:
Please Reply if someone has any ideas to it.
PS: Itneeds not tobe MD5 - any other crypto algorithm should do it as well
0 Kudos
Jugoslav_Dujic
Valued Contributor II
3,398 Views
FWIW, Windows has native APIs to do it (not that I know how). See e.g. CryptEncrypt in documentation (but follow the link to chapter heading & click "Locate" button to see entire chapter).
Jugoslav
0 Kudos
Steven_L_Intel1
Employee
3,398 Views
Attached is an example of using the Win32 Crypto API, though it doesn't use EncryptHash. Using the hash function would be much simpler than this example, but it will give you some clues as to how to use the API.
0 Kudos
christian_rackl
Beginner
3,398 Views
I did many researches about the cryptography api and developed the following program:
Code:
	program hash

		character*32 string

		string = "c"
		
		call md5(trim(string))


	end program


	subroutine md5(string)
		USE DFWINTY
		USE ADVAPI32
		IMPLICIT NONE

		character*(*) string

		integer(HANDLE) :: hCryptProv
		integer(HANDLE) :: hHash
		integer(DWORD) :: ret

		character*32 myhash

		integer(DWORD) :: HASHSIZE

		HASHSIZE = 32

!		Create handle to CSP
		ret = CryptAcquireContext(hCryptProv, NULL_CHARACTER, NULL_CHARACTER, PROV_RSA_FULL, 0)
		if (ret == FALSE) then
			write(6,'("ERROR: CryptAcquireContext")')
			STOP
		endif

!		Create Hash Handle
		ret = CryptCreateHash (hCryptProv, CALG_MD5, 0, 0, hHash)
		if (ret == FALSE) then
			write(6,'("ERROR: CryptCreateHash")')
			STOP
		endif

!		Hash Data
		write(6,'("String: >",a,"< ",/,"Length: ",i8)') string, len(string)
		ret = CryptHashData (hHash, string, len(string), 0)
		if (ret == FALSE) then
			write(6,'("ERROR: CryptHashData")')
			STOP
		endif

!		Finish Crypting
		ret = CryptGetHashParam (hHash, HP_HASHVAL, myhash, HASHSIZE, 0)
		if (ret == FALSE) then
			write(6,'("ERROR: CryptGetHashParam")')
			STOP
		endif
		write(6,'("Hashlength: ",i8,/,"Hash: ",z32)') HASHSIZE,myhash



	end subroutine
This program really(!) creates some sort of hash chacksum........
but if you try to create the checksum with another program (i tried php) i get other values!!
Does anyone know what I've done wrong??
Help appreciated!
0 Kudos
christian_rackl
Beginner
3,398 Views
Problem Solved!
Everything works fine now!
THX
0 Kudos
onkelhotte
New Contributor II
3,398 Views
Does anybody know how to calculate a md5 hash or has a source code?

Steves example isnt here any more and the code from the original poster doesnt compute the right md5 hash. Its bad that he hasnt told us, what he did wrong, I cannot find the error.

Markus
0 Kudos
Steven_L_Intel1
Employee
3,398 Views
The sample I referenced is now part of the product. If all you want to do is find the MD5 hash of a file, I recommend HashTab.

I once tried to write my own Fortran version of MD5 but could not duplicate the C results. There is some aspect of it that escaped me.
0 Kudos
onkelhotte
New Contributor II
3,398 Views
Hi Steve,
I want to get the md5 hash of a string, so the example wont help.

But your example can be useful in another way!

Does anybody knows how to retrieve the md5 hash of a string?
I could program the pseudo-code like it is shown in wikipedia, but I dont want to ;-)

Markus
0 Kudos
onkelhotte
New Contributor II
3,398 Views
Okay, here comes some messy code.. It could be more elegant, but it works :-)

Its an implemtation of the pseudo code, that I found on Wikipedia.

[bash]! **********************************************************************
character*32 function md5(string)
! ---------------------------------------------------------------------*
!     Programmierer    : VEZ2/Pieper                                   *
!     Version          : 1.0                                           *
!     letzte nderung  : 07.05.2010                                    *
!     Aufgabe          : Erzeugt aus einem String einen MD5 Hashwert   *
! **********************************************************************

implicit none

character*(*) string
character*((int(len(string)/64)+1)*64) newString
character*8 wtmp

integer(kind=4) j,n1,n2,n3,n4,umdrehen,pos
integer(kind=4) r(64),k(64),h0,h1,h2,h3,a,b,c,d,f,g,temp,w(16),leftrotate,i,intLen
integer(kind=8) hoch32
real(kind=8) sinus,absolut,real8i

r = [7, 12, 17, 22,  7, 12, 17, 22,  7, 12, 17, 22,  7, 12, 17, 22, 5,  9, 14, 20,  5,  9, 14, 20,  5,  9, 14, 20,  5,  9, 14, 20, 4, 11, 16, 23,  4, 11, 16, 23,  4, 11, 16, 23,  4, 11, 16, 23, 6, 10, 15, 21,  6, 10, 15, 21,  6, 10, 15, 21,  6, 10, 15, 21]

do i=1,64
    real8i = floatk(int8(i))
    sinus = dsin(real8i)
    absolut = dabs(sinus)
    hoch32 = 2.**32.
    k(i) = int8(absolut * floatk(hoch32))
end do

h0 = #67452301
h1 = #EFCDAB89
h2 = #98BADCFE
h3 = #10325476

j = len(string)+1
newString(:j) = string // char(128)
i = mod(j, 64)
do while(i /= 56)
    j = j + 1
    newString(j:j) = char(0)
    i = mod(j, 64)
end do

intLen = len(string)*8
do i = 0,3
    temp = intLen .and. #FF
    j = j + 1
    newString(j:j) = char(temp)
    intLen = shiftr(intLen, 8)
end do

do i = 1,4
    j = j + 1
    newString(j:j) = char(0)
end do

do i = 1,int(len(newString)/64)

    do j = 1,16
        pos = (j-1)*4+(i-1)*64
        n1 = ichar(newString(4+pos:4+pos))
        n2 = ichar(newString(3+pos:3+pos))
        n3 = ichar(newString(2+pos:2+pos))
        n4 = ichar(newString(1+pos:1+pos))
        
        write(wtmp,'(4(z2.2))') n1,n2,n3,n4
        read(wtmp,'(z8)') w(j)
    end do

    a = h0
    b = h1
    c = h2
    d = h3

    do j = 1,64
        if (j >= 1 .and. j <= 16) then
            f = (b .and. c) .or. ((.not. b) .and. d)
            g = j
        else if (j >= 17 .and. j <= 32) then
            f = (d .and. b) .or. ((.not. d) .and. c)
            g = mod(5*(j-1) + 1, 16) + 1
        else if (j >= 33 .and. j <= 48) then
            f = ieor(b, ieor(c, d))
            g = mod(3*(j-1) + 5, 16) + 1
        else if (j >= 49 .and. j <= 64) then
            f = ieor(c, (b .or. (.not. d)))
            g = mod(7*(j-1), 16) + 1
        end if
        
        temp = d
        d = c
        c = b
        b = b + leftrotate((a + f + k(j) + w(g)) , r(j))
        a = temp
    end do

    h0 = h0 + a
    h1 = h1 + b
    h2 = h2 + c
    h3 = h3 + d
end do
h0 = umdrehen(h0)
h1 = umdrehen(h1)
h2 = umdrehen(h2)
h3 = umdrehen(h3)

write(md5,'(4(z8))') h0,h1,h2,h3
return

end function md5
!
!
! **********************************************************************
integer(kind=4) function leftrotate (x, c)
! ---------------------------------------------------------------------*
!     Programmierer    : VEZ2/Pieper                                   *
!     Version          : 1.0                                           *
!     letzte nderung  : 07.05.2010                                    *
!     Aufgabe          : Fhrt ein Leftrotate der Bits durch           *
! **********************************************************************

implicit none

integer(kind=4) x,c,result1,result2

result1 = shiftl(x,c)
result2 = shiftr(x, (32-c))

leftrotate = result1 .or. result2

return
end function leftrotate
!
!
! **********************************************************************
integer(kind=4) function umdrehen(zahl)
! ---------------------------------------------------------------------*
!     Programmierer    : VEZ2/Pieper                                   *
!     Version          : 1.0                                           *
!     letzte nderung  : 07.05.2010                                    *
!     Aufgabe          : Macht aus Big Endian -> Little Endian Bits    *
! **********************************************************************

implicit none

integer(kind=4) i,tmp,zahl

umdrehen = 0
do i = 1,4
    umdrehen = shiftl(umdrehen, 8)
    tmp = zahl .and. #FF
    umdrehen = umdrehen + tmp;
    zahl = shiftr(zahl, 8)
end do

return
end function umdrehen[/bash]
0 Kudos
onkelhotte
New Contributor II
3,398 Views
There is one little thing to do, instead if a "0" there is only a blank " " in the generated md5 hash.

So the have to replace " " with "0" and your md5 is just fine.

Markus
0 Kudos
Reply