ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/simulation_module.F90
Revision: 252
Committed: Tue Jan 28 22:16:55 2003 UTC (21 years, 5 months ago) by chuckv
File size: 6317 byte(s)
Log Message:
Force loops seems to work, velocitize never being called....

File Contents

# Content
1 module simulation
2 use definitions, ONLY :dp
3 #ifdef IS_MPI
4 use mpiSimulation
5 #endif
6
7 implicit none
8 PRIVATE
9
10
11
12 type, public :: simtype
13 PRIVATE
14 ! SEQUENCE
15 !! Number of particles on this processor
16 integer :: nLRparticles
17 !! Periodic Box
18 real ( kind = dp ), dimension(3) :: box
19 !! List Cutoff
20 real ( kind = dp ) :: rlist = 0.0_dp
21 !! Radial cutoff
22 real ( kind = dp ) :: rcut = 0.0_dp
23 !! List cutoff squared
24 real ( kind = dp ) :: rlistsq = 0.0_dp
25 !! Radial Cutoff squared
26 real ( kind = dp ) :: rcutsq = 0.0_dp
27 !! Radial Cutoff^6
28 real ( kind = dp ) :: rcut6 = 0.0_dp
29
30 end type simtype
31
32 type (simtype), public :: thisSim
33 !! Tag for MPI calculations
34 integer, allocatable, dimension(:) :: tag
35
36 #ifdef IS_MPI
37 integer, allocatable, dimension(:) :: tag_row
38 integer, allocatable, dimension(:) :: tag_column
39 #endif
40
41 !! WARNING: use_pbc hardcoded, fixme
42 logical :: use_pbc = .true.
43 logical :: setSim = .false.
44
45 !! array for saving previous positions for neighbor lists.
46 real( kind = dp ), allocatable,dimension(:,:),save :: q0
47
48
49 public :: check
50 public :: save_nlist
51 public :: wrap
52 public :: getBox
53 public :: getRcut
54 public :: getRlist
55 public :: getNlocal
56 public :: setSimulation
57 ! public :: setRcut
58
59 interface wrap
60 module procedure wrap_1d
61 module procedure wrap_3d
62 end interface
63
64 interface getBox
65 module procedure getBox_3d
66 module procedure getBox_dim
67 end interface
68
69
70
71
72
73
74
75
76
77
78 contains
79
80 subroutine setSimulation(nLRParticles,box,rlist,rcut)
81 integer, intent(in) :: nLRParticles
82 real(kind = dp ), intent(in), dimension(3) :: box
83 real(kind = dp ), intent(in) :: rlist
84 real(kind = dp ), intent(in) :: rcut
85 integer :: alloc_stat
86 if( setsim ) return ! simulation is already initialized
87 setSim = .true.
88
89 thisSim%nLRParticles = nLRParticles
90 thisSim%box = box
91 thisSim%rlist = rlist
92 thisSim%rcut = rcut
93 thisSim%rcutsq = rcut * rcut
94 thisSim%rcut6 = thisSim%rcutsq * thisSim%rcutsq * thisSim%rcutsq
95
96 if (.not. allocated(q0)) then
97 allocate(q0(3,nLRParticles),stat=alloc_stat)
98 endif
99 end subroutine setSimulation
100
101 function getNparticles() result(nparticles)
102 integer :: nparticles
103 nparticles = thisSim%nLRparticles
104 end function getNparticles
105
106
107 subroutine change_box_size(new_box_size)
108 real(kind=dp), dimension(3) :: new_box_size
109
110 thisSim%box = new_box_size
111
112 end subroutine change_box_size
113
114
115 function getBox_3d() result(thisBox)
116 real( kind = dp ), dimension(3) :: thisBox
117 thisBox = thisSim%box
118 end function getBox_3d
119
120 function getBox_dim(dim) result(thisBox)
121 integer, intent(in) :: dim
122 real( kind = dp ) :: thisBox
123
124 thisBox = thisSim%box(dim)
125 end function getBox_dim
126
127 subroutine check(q,update_nlist)
128 real( kind = dp ), dimension(:,:) :: q
129 integer :: i
130 real( kind = DP ) :: dispmx
131 logical, intent(out) :: update_nlist
132 real( kind = DP ) :: dispmx_tmp
133 real( kind = dp ) :: skin_thickness
134 integer :: natoms
135
136 natoms = thisSim%nLRparticles
137 skin_thickness = thisSim%rlist
138 dispmx = 0.0E0_DP
139 !! calculate the largest displacement of any atom in any direction
140
141 #ifdef MPI
142 dispmx_tmp = 0.0E0_DP
143 do i = 1, thisSim%nLRparticles
144 dispmx_tmp = max( abs ( q(1,i) - q0(1,i) ), dispmx )
145 dispmx_tmp = max( abs ( q(2,i) - q0(2,i) ), dispmx )
146 dispmx_tmp = max( abs ( q(3,i) - q0(3,i) ), dispmx )
147 end do
148 call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
149 mpi_max,mpi_comm_world,mpi_err)
150 #else
151
152 do i = 1, thisSim%nLRparticles
153 dispmx = max( abs ( q(1,i) - q0(1,i) ), dispmx )
154 dispmx = max( abs ( q(2,i) - q0(2,i) ), dispmx )
155 dispmx = max( abs ( q(3,i) - q0(3,i) ), dispmx )
156 end do
157 #endif
158
159 !! a conservative test of list skin crossings
160 dispmx = 2.0E0_DP * sqrt (3.0E0_DP * dispmx * dispmx)
161
162 update_nlist = (dispmx.gt.(skin_thickness))
163
164 end subroutine check
165
166 subroutine save_nlist(q)
167 real(kind = dp ), dimension(:,:), intent(in) :: q
168 integer :: list_size
169
170
171 list_size = size(q)
172
173 if (.not. allocated(q0)) then
174 allocate(q0(3,list_size))
175 else if( list_size > size(q0)) then
176 deallocate(q0)
177 allocate(q0(3,list_size))
178 endif
179
180 q0 = q
181
182 end subroutine save_nlist
183
184
185 function wrap_1d(r,dim) result(this_wrap)
186
187
188 real( kind = DP ) :: r
189 real( kind = DP ) :: this_wrap
190 integer :: dim
191
192 if (use_pbc) then
193 ! this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
194 this_wrap = r - thisSim%box(dim)*nint(r/thisSim%box(dim))
195 else
196 this_wrap = r
197 endif
198
199 return
200 end function wrap_1d
201
202 function wrap_3d(r) result(this_wrap)
203 real( kind = dp ), dimension(3), intent(in) :: r
204 real( kind = dp ), dimension(3) :: this_wrap
205
206
207 if (use_pbc) then
208 ! this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
209 this_wrap = r - thisSim%box*nint(r/thisSim%box)
210 else
211 this_wrap = r
212 endif
213 end function wrap_3d
214
215
216
217 subroutine getRcut(thisrcut,rcut2,rcut6,status)
218 real( kind = dp ), intent(out) :: thisrcut
219 real( kind = dp ), intent(out), optional :: rcut2
220 real( kind = dp ), intent(out), optional :: rcut6
221 integer, optional :: status
222
223 if (present(status)) status = 0
224
225 if (.not.setSim ) then
226 if (present(status)) status = -1
227 return
228 end if
229
230 thisrcut = thisSim%rcut
231 if(present(rcut2)) rcut2 = thisSim%rcutsq
232 if(present(rcut6)) rcut6 = thisSim%rcut6
233
234 end subroutine getRcut
235
236
237
238
239 subroutine getRlist(thisrlist,rlist2,status)
240 real( kind = dp ), intent(out) :: thisrlist
241 real( kind = dp ), intent(out), optional :: rlist2
242
243 integer, optional :: status
244
245 if (present(status)) status = 0
246
247 if (.not.setSim ) then
248 if (present(status)) status = -1
249 return
250 end if
251
252 thisrlist = thisSim%rlist
253 if(present(rlist2)) rlist2 = thisSim%rlistsq
254
255 end subroutine getRlist
256
257
258
259 pure function getNlocal() result(nlocal)
260 integer :: nlocal
261 nlocal = thisSim%nLRparticles
262 end function getNlocal
263
264
265
266 end module simulation