module readdata contains subroutine readdcd(maxframes,maxatoms,x,y,z,xbox,ybox,zbox,natoms,nframes) use cudafor implicit none integer i,j integer maxframes,maxatoms double precision d(6),xbox,ybox,zbox real*4, managed, allocatable :: x(:,:) real*4, managed, allocatable :: y(:,:) real*4, managed, allocatable :: z(:,:) real*4 dummyr integer*4 nset, natoms, dummyi,nframes,tframes character*4 dummyc open(10,file='/home/hpclabs/manish/input/alk.traj.dcd',status='old',form='unformatted') read(10) dummyc, tframes,(dummyi,i=1,8),dummyr, (dummyi,i=1,9) read(10) dummyi, dummyr,dummyr read(10) natoms print*,"Total number of frames and atoms are",tframes,natoms allocate ( x(maxframes,natoms) ) allocate ( y(maxframes,natoms) ) allocate ( z(maxframes,natoms) ) do i = 1,nframes read(10) (d(j),j=1, 6) read(10) (x(i,j),j=1,natoms) read(10) (y(i,j),j=1,natoms) read(10) (z(i,j),j=1,natoms) end do xbox=d(1) ybox=d(3) zbox=d(6) print*,"File reading is done: xbox,ybox,zbox",xbox,ybox,zbox return end subroutine readdcd attributes(global) subroutine pair_calculation( x,y,z,g,natoms,nframes,xbox,ybox,zbox,del,cut) use cudafor implicit none real*4 :: x(:,:) real*4 :: y(:,:) real*4 :: z(:,:) double precision,intent(inout) :: g(:) integer, value :: nframes,natoms,ind double precision, value :: xbox,ybox,zbox,del,cut integer i,j,iconf double precision dx,dy,dz,r,oldvalue i = (blockIdx%x-1)*blockDim%x+threadIdx%x j = (blockIdx%y-1)*blockDim%y+threadIdx%y if ( i == 1 .and. j == 1) then print *, natoms,nframes,xbox,ybox,zbox,del,cut, x(1,1), y(1,1), z(1,1), g(1) end if do iconf=1,nframes if(i<=natoms .and. j<=natoms) then dx=x(iconf,i)-x(iconf,j) dy=y(iconf,i)-y(iconf,j) dz=z(iconf,i)-z(iconf,j) dx=dx-nint(dx/xbox)*xbox dy=dy-nint(dy/ybox)*ybox dz=dz-nint(dz/zbox)*zbox r=dsqrt(dx**2+dy**2+dz**2) ind=int(r/del)+1 if(r>>(x,y,z,g,natoms,nframes,xbox,ybox,zbox,del,cut) istat = cudaDeviceSynchronize() if(istat /= 0) then print *, "Error" end if !do iconf=1,nframes ! do i=1,natoms ! do j=1,natoms ! if ( i == 1 .and. j == 1) then ! print *, natoms,nframes,xbox,ybox,zbox,del,cut, x(1,1), y(1,1), z(1,1), g(1) ! end if ! dx=x(iconf,i)-x(iconf,j) ! dy=y(iconf,i)-y(iconf,j) ! dz=z(iconf,i)-z(iconf,j) ! dx=dx-nint(dx/xbox)*xbox ! dy=dy-nint(dy/ybox)*ybox ! dz=dz-nint(dz/zbox)*zbox ! r=dsqrt(dx**2+dy**2+dz**2) ! ind=int(r/del)+1 ! !if (ind.le.nbin) then ! if(r