-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathRDF_mod.f90
171 lines (140 loc) · 5.37 KB
/
RDF_mod.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
!------------------------- m_RDF module --------------------------------------
!--- UNDER CONSTRUCTION / NOT COMPLETE
!-- this is a self contained module for calculating RDFs during an MD run
!-- it is designed to be callable by any MD program
!-- it currently contains subroutines for OO, HH, OH RDFs and average geometry
!-----------------------------------------------------------------------------
module RDF_mod
Implicit None
real,dimension(3), save :: length, halflength
Integer,save :: Ndiv
real,save :: delta, qO, qH, rOM
integer :: nsteps
integer,save :: Na, Nmol
real,parameter :: e2coul=1.60217646e-19
real,parameter :: ang2m=1e-10
character(120) :: fileheader
real,dimension(:),allocatable :: gKr, gKr2, histOO, histOH, histHH,
contains
subroutine calc_geometry
Nmol =
do i = 1, Nmol
sum_HH =
sum_OH =
sum_OO =
sum_HOH =
enddo
endsubroutine
!-----------------------------------------------------------------------
!------------------------ O-O RDF -------------------------------------
!-----------------------------------------------------------------------
subroutine RDF_OO(xa)
implicit none
integer,intent(in) :: Nmol
real,dimension(3,Nmol),intent(in) :: xa
real,dimension(Ndiv),intent(out) :: hist
! INTERNAL VARS
real :: rho, vol, distance, tmp, histgas
integer :: ia, ja, ix, i, Ntot ! loop flags
! ARRAYS
real,dimension(Ndiv) :: histliquid ! pre-normalization histogram
histliquid = 0.0d0
rho = Nmol / (length(1)*length(2)*length(3))
! ADJUST COORDINATES FOR PERIODIC BOUNDING
do ia=1,Nmol-1 ! do for every molecule
do ja=ia+1,Nmol ! to every other molecule
distance=0.0d0
do ix=1,3
if(abs(xa(ix,ia)-xa(ix,ja)) >= minval(halflength)) then
if(xa(ix,ia)-xa(ix,ja) > 0) then
tmp=xa(ix,ja)+minval(halflength)*2.0d0
else
tmp=xa(ix,ja)-minval(halflength)*2.0d0
end if
distance=distance+(xa(ix,ia)-tmp)**2
else
tmp=xa(ix,ja)
distance=distance+(xa(ix,ia)-tmp)**2
endif
enddo
distance=sqrt(distance)
! ACTUALIZE HISTOGRAM
if(distance .lt. minval(halflength)) then
call updatehist(distance,histliquid)
endif
enddo
enddo
! NORMALIZE HISTOGRAM
do i=1,Ndiv
vol=(4.0d0/3.0d0)*pi*((i*delta)**3-((i-1)*delta)**3)
histgas=rho*vol
hist(i)= hist(i) + histliquid(i)/(histgas*Nmol)
enddo
end subroutine RDF_OO
!-------------------------------------------------------------------------------
!-------------------- OH RDF --------------------------------------------------
!-------------------------------------------------------------------------------
subroutine RDF_OH(Nmol, Oxy, Hydro, hist)
implicit none
! DUMMY ARGUMENTS
integer,intent(in) :: Nmol
real,dimension(3,Nmol),intent(in) :: Oxy
real,dimension(3,2*Nmol),intent(in) :: Hydro
real,dimension(Ndiv),intent(inout) :: hist
! INTERNAL VARS
real :: rho, vol, distance, tmp, histgas
integer :: ia, ja, ix, i ! loop flags
! ARRAYS
real,dimension(Ndiv) :: histliquid ! pre-normalization histogram
! INITIALIZE VARIABLES
histliquid = 0.0d0
rho = 2*Nmol / (length(1)*length(2)*length(3))
! ADJUST FOR PERIODIC BOUNDING AND CALCULATE DISTANCE
do ia=1,Nmol
do ja=1,2*Nmol
distance=0.0d0
do ix=1,3
if(abs(Oxy(ix,ia)-Hydro(ix,ja)) >= minval(halflength)) then
if(Oxy(ix,ia)-Hydro(ix,ja) > 0) then
tmp=Hydro(ix,ja)+minval(halflength)*2.0d0
else
tmp=Hydro(ix,ja)-minval(halflength)*2.0d0
end if
distance=distance+(Oxy(ix,ia)-tmp)**2
else
tmp=Hydro(ix,ja)
distance=distance+(Oxy(ix,ia)-tmp)**2
endif
enddo
distance=sqrt(distance)
! ACTUALIZE HISTOGRAM
if(distance .lt. minval(halflength)) then
call updatehist(distance,histliquid)
endif
enddo
enddo
! NORMALIZE HISTOGRAM
do i=1,Ndiv
vol=(4.0d0/3.0d0)*pi*((i*delta)**3-((i-1)*delta)**3)
histgas=rho*vol
hist(i)= hist(i) + histliquid(i)/(histgas*2*Nmol)
enddo
end subroutine RDF_OH
!-----------------------------------------------------------------------
!------------- determine how histogram is binned ----------------------
!-----------------------------------------------------------------------
subroutine updatehist(x, hist)
implicit none
real :: x,lever
real, dimension(Ndiv) :: hist
integer :: i,j,count
count=floor(x/delta)
!lever=mod(x,delta)/delta
!there is a factor of two because each distance is for 2 atoms
if (count .gt. 0) then
histliquid(count) = hist(count) + 2
!histliquid(count)=hist(count)+2.0d0*(1.0d0-lever)
!histliquid(count+1)=hist(count+1)+2.0d0*lever
endif
end subroutine updatehist
end module