rdf.f90 4.3 KB

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