rdf_orig.f90 4.6 KB

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