rdf.f90 5.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187
  1. module readdata
  2. contains
  3. subroutine readdcd(maxframes,maxatoms,x,y,z,xbox,ybox,zbox,natoms,nframes)
  4. use cudafor
  5. implicit none
  6. integer i,j
  7. integer maxframes,maxatoms
  8. double precision d(6),xbox,ybox,zbox
  9. real*4, managed, allocatable :: x(:,:)
  10. real*4, managed, allocatable :: y(:,:)
  11. real*4, managed, allocatable :: z(:,:)
  12. real*4 dummyr
  13. integer*4 nset, natoms, dummyi,nframes,tframes
  14. character*4 dummyc
  15. open(10,file='../input/alk.traj.dcd',status='old',form='unformatted')
  16. read(10) dummyc, tframes,(dummyi,i=1,8),dummyr, (dummyi,i=1,9)
  17. read(10) dummyi, dummyr,dummyr
  18. read(10) natoms
  19. print*,"Total number of frames and atoms are",tframes,natoms
  20. allocate ( x(maxframes,natoms) )
  21. allocate ( y(maxframes,natoms) )
  22. allocate ( z(maxframes,natoms) )
  23. do i = 1,nframes
  24. read(10) (d(j),j=1, 6)
  25. read(10) (x(i,j),j=1,natoms)
  26. read(10) (y(i,j),j=1,natoms)
  27. read(10) (z(i,j),j=1,natoms)
  28. end do
  29. xbox=d(1)
  30. ybox=d(3)
  31. zbox=d(6)
  32. print*,"File reading is done: xbox,ybox,zbox",xbox,ybox,zbox
  33. return
  34. end subroutine readdcd
  35. ! Todo: Add global attribute
  36. attributes() subroutine pair_calculation( x,y,z,g,natoms,nframes,xbox,ybox,zbox,del,cut)
  37. use cudafor
  38. implicit none
  39. real*4 :: x(:,:)
  40. real*4 :: y(:,:)
  41. real*4 :: z(:,:)
  42. double precision,intent(inout) :: g(:)
  43. integer, value :: nframes,natoms,ind
  44. double precision, value :: xbox,ybox,zbox,del,cut
  45. integer i,j,iconf
  46. double precision dx,dy,dz,r,oldvalue
  47. !Todo: Add indexing
  48. i =
  49. j =
  50. do iconf=1,nframes
  51. if(i<=natoms .and. j<=natoms) then
  52. dx=x(iconf,i)-x(iconf,j)
  53. dy=y(iconf,i)-y(iconf,j)
  54. dz=z(iconf,i)-z(iconf,j)
  55. dx=dx-nint(dx/xbox)*xbox
  56. dy=dy-nint(dy/ybox)*ybox
  57. dz=dz-nint(dz/zbox)*zbox
  58. r=dsqrt(dx**2+dy**2+dz**2)
  59. ind=int(r/del)+1
  60. if(r<cut)then
  61. !Todo: Add atomic Add function call
  62. g(ind) = g(ind) + 1.0d0
  63. endif
  64. endif
  65. end do
  66. return
  67. end subroutine pair_calculation
  68. end module readdata
  69. program rdf
  70. use readdata
  71. use cudafor
  72. implicit none
  73. integer n,i,j,iconf,ind,istat
  74. integer natoms,nframes,nbin
  75. integer maxframes,maxatoms
  76. type(dim3) :: blocks, threads
  77. parameter (maxframes=10,maxatoms=60000,nbin=2000)
  78. ! Todo: Make the array use managed for variables being used in kernel
  79. real*4, allocatable :: x(:,:)
  80. real*4, allocatable :: y(:,:)
  81. real*4, allocatable :: z(:,:)
  82. double precision, allocatable :: g(:)
  83. double precision dx,dy,dz
  84. double precision xbox,ybox,zbox,cut
  85. double precision vol,r,del,s2,s2bond
  86. double precision rho,gr,lngr,lngrbond,pi,const,nideal,rf
  87. double precision rlower,rupper
  88. character atmnm*4
  89. real*4 start,finish
  90. open(23,file='RDF.dat',status='unknown')
  91. open(24,file='Pair_entropy.dat',status='unknown')
  92. nframes=10
  93. call cpu_time(start)
  94. print*,"Going to read coordinates"
  95. call nvtxStartRange("Read File")
  96. call readdcd(maxframes,maxatoms,x,y,z,xbox,ybox,zbox,natoms,nframes)
  97. call nvtxEndRange
  98. allocate ( g(nbin) )
  99. do i=1,nbin
  100. g(i) = 0.0d0
  101. end do
  102. pi=dacos(-1.0d0)
  103. vol=xbox*ybox*zbox
  104. rho=dble(natoms)/vol
  105. del=xbox/dble(2.0*nbin)
  106. write(*,*) "bin width is : ",del
  107. cut = dble(xbox * 0.5);
  108. threads = dim3(16,16,1)
  109. blocks = dim3(ceiling(real(natoms)/threads%x), ceiling(real(natoms)/threads%y),1)
  110. print *, "natoms:, Grid Size:", threads, blocks
  111. call nvtxStartRange("Pair Calculation")
  112. call pair_calculation<<<blocks,threads>>>(x,y,z,g,natoms,nframes,xbox,ybox,zbox,del,cut)
  113. istat = cudaDeviceSynchronize()
  114. if(istat /= 0) then
  115. print *, "Error"
  116. end if
  117. call nvtxEndRange
  118. s2=0.01d0
  119. s2bond=0.01d0
  120. const=(4.0d0/3.0d0)*pi*rho
  121. call nvtxStartRange("Entropy Calculation")
  122. do i=1,nbin
  123. rlower=dble((i-1)*del)
  124. rupper=rlower+del
  125. nideal=const*(rupper**3-rlower**3)
  126. g(i)=g(i)/(dble(nframes)*dble(natoms)*nideal)
  127. r=dble(i)*del
  128. if (r.lt.2.0) then
  129. gr=0.0
  130. else
  131. gr=g(i)
  132. endif
  133. if (gr.lt.1e-5) then
  134. lngr=0.0
  135. else
  136. lngr=dlog(gr)
  137. endif
  138. if (g(i).lt.1e-6) then
  139. lngrbond=0.01
  140. else
  141. lngrbond=dlog(g(i))
  142. endif
  143. s2=s2-2*pi*rho*((gr*lngr)-gr+1)*del*r**2.0
  144. s2bond=s2bond-2*pi*rho*((g(i)*lngrbond)-g(i)+1)*del*r*r
  145. rf=dble(i-.5)*del
  146. write(23,*) rf,g(i)
  147. enddo
  148. write(24,*)"s2 : ",s2
  149. write(24,*)"s2bond : ",s2bond
  150. call cpu_time(finish)
  151. print*,"starting at time",start,"and ending at",finish
  152. stop
  153. call nvtxEndRange
  154. deallocate(x,y,z,g)
  155. end