ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/branches/development/src/UseTheForce/doForces.F90
Revision: 1532
Committed: Wed Dec 29 19:59:21 2010 UTC (14 years, 4 months ago) by gezelter
File size: 40574 byte(s)
Log Message:
Added MAW to the C++ side, removed a whole bunch more fortran. 

File Contents

# Content
1 !!
2 !! Copyright (c) 2005, 2009 The University of Notre Dame. All Rights Reserved.
3 !!
4 !! The University of Notre Dame grants you ("Licensee") a
5 !! non-exclusive, royalty free, license to use, modify and
6 !! redistribute this software in source and binary code form, provided
7 !! that the following conditions are met:
8 !!
9 !! 1. Redistributions of source code must retain the above copyright
10 !! notice, this list of conditions and the following disclaimer.
11 !!
12 !! 2. Redistributions in binary form must reproduce the above copyright
13 !! notice, this list of conditions and the following disclaimer in the
14 !! documentation and/or other materials provided with the
15 !! distribution.
16 !!
17 !! This software is provided "AS IS," without a warranty of any
18 !! kind. All express or implied conditions, representations and
19 !! warranties, including any implied warranty of merchantability,
20 !! fitness for a particular purpose or non-infringement, are hereby
21 !! excluded. The University of Notre Dame and its licensors shall not
22 !! be liable for any damages suffered by licensee as a result of
23 !! using, modifying or distributing the software or its
24 !! derivatives. In no event will the University of Notre Dame or its
25 !! licensors be liable for any lost revenue, profit or data, or for
26 !! direct, indirect, special, consequential, incidental or punitive
27 !! damages, however caused and regardless of the theory of liability,
28 !! arising out of the use of or inability to use software, even if the
29 !! University of Notre Dame has been advised of the possibility of
30 !! such damages.
31 !!
32 !! SUPPORT OPEN SCIENCE! If you use OpenMD or its source code in your
33 !! research, please cite the appropriate papers when you publish your
34 !! work. Good starting points are:
35 !!
36 !! [1] Meineke, et al., J. Comp. Chem. 26, 252-271 (2005).
37 !! [2] Fennell & Gezelter, J. Chem. Phys. 124, 234104 (2006).
38 !! [3] Sun, Lin & Gezelter, J. Chem. Phys. 128, 24107 (2008).
39 !! [4] Vardeman & Gezelter, in progress (2009).
40 !!
41
42 !! doForces.F90
43 !! module doForces
44 !! Calculates Long Range forces.
45
46 !! @author Charles F. Vardeman II
47 !! @author Matthew Meineke
48 !! @version $Id$, $Date$, $Name: not supported by cvs2svn $, $Revision$
49
50
51 module doForces
52 use force_globals
53 use simulation
54 use definitions
55 use neighborLists
56 use status
57 use ISO_C_BINDING
58
59 #ifdef IS_MPI
60 use mpiSimulation
61 #endif
62
63 implicit none
64 PRIVATE
65
66 real(kind=dp), external :: get_cutoff
67
68 #define __FORTRAN90
69 #include "UseTheForce/DarkSide/fInteractionMap.h"
70
71 INTEGER, PARAMETER:: PREPAIR_LOOP = 1
72 INTEGER, PARAMETER:: PAIR_LOOP = 2
73
74 logical, save :: haveNeighborList = .false.
75 logical, save :: haveSIMvariables = .false.
76 logical, save :: haveCutoffs = .false.
77 logical, save :: haveSkinThickness = .false.
78
79 logical, save :: SIM_uses_DirectionalAtoms
80 logical, save :: SIM_uses_MetallicAtoms
81 logical, save :: SIM_requires_skip_correction
82 logical, save :: SIM_requires_self_correction
83 logical, save :: SIM_uses_PBC
84 logical, save :: SIM_uses_AtomicVirial
85
86 real(kind=dp), save :: rCut, rSwitch, rList, rListSq, rCutSq
87 real(kind=dp), save :: skinThickness
88 logical, save :: shifted_pot
89 logical, save :: shifted_force
90
91 public :: init_FF
92 public :: setCutoffs
93 public :: setSkinThickness
94 public :: do_force_loop
95
96 #ifdef PROFILE
97 public :: getforcetime
98 real, save :: forceTime = 0
99 real :: forceTimeInitial, forceTimeFinal
100 integer :: nLoops
101 #endif
102
103 contains
104
105 subroutine setCutoffs(rc, rsw, sp, sf)
106
107 real(kind=dp),intent(in) :: rc, rsw
108 integer, intent(in) :: sp, sf
109 character(len = statusMsgSize) :: errMsg
110 integer :: localError
111
112 rCut = rc
113 rSwitch = rsw
114 rCutsq = rCut * rCut
115
116 if (haveSkinThickness) then
117 rList = rCut + skinThickness
118 rListSq = rListSq
119 endif
120
121 if (sp .ne. 0) then
122 shifted_pot = .true.
123 else
124 shifted_pot = .false.
125 endif
126 if (sf .ne. 0) then
127 shifted_force = .true.
128 else
129 shifted_force = .false.
130 endif
131
132 if (abs(rCut - rSwitch) .lt. 0.0001) then
133 if (shifted_force) then
134 write(errMsg, *) &
135 'cutoffRadius and switchingRadius are set to the', newline &
136 // tab, 'same value. OpenMD will use shifted force', newline &
137 // tab, 'potentials instead of switching functions.'
138
139 call handleInfo("setCutoffs", errMsg)
140 else
141 write(errMsg, *) &
142 'cutoffRadius and switchingRadius are set to the', newline &
143 // tab, 'same value. OpenMD will use shifted', newline &
144 // tab, 'potentials instead of switching functions.'
145
146 call handleInfo("setCutoffs", errMsg)
147
148 shifted_pot = .true.
149 endif
150
151 endif
152
153 localError = 0
154 call set_switch(rSwitch, rCut)
155 call setHmatDangerousRcutValue(rCut)
156
157 haveCutoffs = .true.
158 end subroutine setCutoffs
159
160 subroutine setSkinThickness( thisSkin )
161
162 real(kind=dp), intent(in) :: thisSkin
163
164 skinThickness = thisSkin
165 haveSkinThickness = .true.
166
167 if (haveCutoffs) then
168 rList = rCut + skinThickness
169 rListSq = rList * rList
170 endif
171
172 end subroutine setSkinThickness
173
174 subroutine setSimVariables()
175 SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
176 SIM_uses_MetallicAtoms = SimUsesMetallicAtoms()
177 SIM_requires_skip_correction = SimRequiresSkipCorrection()
178 SIM_requires_self_correction = SimRequiresSelfCorrection()
179 SIM_uses_PBC = SimUsesPBC()
180 SIM_uses_AtomicVirial = SimUsesAtomicVirial()
181
182 haveSIMvariables = .true.
183 return
184 end subroutine setSimVariables
185
186 subroutine doReadyCheck(error)
187 integer, intent(out) :: error
188 integer :: myStatus
189
190 error = 0
191
192 if (.not. haveSIMvariables) then
193 call setSimVariables()
194 endif
195
196 if (.not. haveCutoffs) then
197 write(default_error, *) 'cutoffs have not been set in doForces!'
198 error = -1
199 return
200 endif
201
202 if (.not. haveSkinThickness) then
203 write(default_error, *) 'skin thickness has not been set in doForces!'
204 error = -1
205 return
206 endif
207
208 if (.not. haveNeighborList) then
209 write(default_error, *) 'neighbor list has not been initialized in doForces!'
210 error = -1
211 return
212 end if
213
214
215 #ifdef IS_MPI
216 if (.not. isMPISimSet()) then
217 write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
218 error = -1
219 return
220 endif
221 #endif
222 return
223 end subroutine doReadyCheck
224
225 subroutine init_FF(thisStat)
226
227 integer :: my_status
228 integer, intent(out) :: thisStat
229
230 !! assume things are copacetic, unless they aren't
231 thisStat = 0
232
233 if (.not. haveNeighborList) then
234 !! Create neighbor lists
235 call expandNeighborList(nLocal, my_status)
236 if (my_Status /= 0) then
237 write(default_error,*) "SimSetup: ExpandNeighborList returned error."
238 thisStat = -1
239 return
240 endif
241 haveNeighborList = .true.
242 endif
243
244 end subroutine init_FF
245
246
247 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
248 !------------------------------------------------------------->
249 subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, particle_pot, &
250 error)
251 !! Position array provided by C, dimensioned by getNlocal
252 real ( kind = dp ), dimension(3, nLocal) :: q
253 !! molecular center-of-mass position array
254 real ( kind = dp ), dimension(3, nGroups) :: q_group
255 !! Rotation Matrix for each long range particle in simulation.
256 real( kind = dp), dimension(9, nLocal) :: A
257 !! Unit vectors for dipoles (lab frame)
258 real( kind = dp ), dimension(9,nLocal) :: eFrame
259 !! Force array provided by C, dimensioned by getNlocal
260 real ( kind = dp ), dimension(3,nLocal) :: f
261 !! Torsion array provided by C, dimensioned by getNlocal
262 real( kind = dp ), dimension(3,nLocal) :: t
263
264 !! Stress Tensor
265 real( kind = dp), dimension(9) :: tau
266 real ( kind = dp ),dimension(LR_POT_TYPES) :: pot
267 real( kind = dp ), dimension(nLocal) :: particle_pot
268 real( kind = dp ), dimension(nLocal) :: skipped_charge
269
270 logical :: in_switching_region
271 #ifdef IS_MPI
272 real( kind = DP ), dimension(LR_POT_TYPES) :: pot_local
273 integer :: nAtomsInRow
274 integer :: nAtomsInCol
275 integer :: nprocs
276 integer :: nGroupsInRow
277 integer :: nGroupsInCol
278 #endif
279 integer :: natoms
280 logical :: update_nlist
281 integer :: i, j, jstart, jend, jnab
282 integer :: istart, iend
283 integer :: ia, jb, atom1, atom2
284 integer :: nlist
285 real( kind = DP ) :: ratmsq, rgrpsq, rgrp, rag, vpair, vij
286 real( kind = DP ) :: sw, dswdr, swderiv, mf
287 real( kind = DP ) :: rVal
288 real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij, fg, dag
289 real(kind=dp) :: rfpot, mu_i
290 real(kind=dp):: rCut
291 integer :: n_in_i, n_in_j, iG, j1
292 logical :: is_dp_i
293 integer :: neighborListSize
294 integer :: listerror, error
295 integer :: localError
296 integer :: propPack_i, propPack_j
297 integer :: loopStart, loopEnd, loop
298 integer :: i1, topoDist
299
300 real(kind=dp) :: skch
301
302 !! initialize local variables
303
304 #ifdef IS_MPI
305 pot_local = 0.0_dp
306 nAtomsInRow = getNatomsInRow(plan_atom_row)
307 nAtomsInCol = getNatomsInCol(plan_atom_col)
308 nGroupsInRow = getNgroupsInRow(plan_group_row)
309 nGroupsInCol = getNgroupsInCol(plan_group_col)
310 #else
311 natoms = nlocal
312 #endif
313
314 call doReadyCheck(localError)
315 if ( localError .ne. 0 ) then
316 call handleError("do_force_loop", "Not Initialized")
317 error = -1
318 return
319 end if
320 call zero_work_arrays()
321
322 ! Gather all information needed by all force loops:
323
324 #ifdef IS_MPI
325
326 call gather(q, q_Row, plan_atom_row_3d)
327 call gather(q, q_Col, plan_atom_col_3d)
328
329 call gather(q_group, q_group_Row, plan_group_row_3d)
330 call gather(q_group, q_group_Col, plan_group_col_3d)
331
332 if (SIM_uses_DirectionalAtoms) then
333 call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
334 call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
335
336 call gather(A, A_Row, plan_atom_row_rotation)
337 call gather(A, A_Col, plan_atom_col_rotation)
338 endif
339
340 #endif
341
342 !! Begin force loop timing:
343 #ifdef PROFILE
344 call cpu_time(forceTimeInitial)
345 nloops = nloops + 1
346 #endif
347
348 loopEnd = PAIR_LOOP
349 if (SIM_uses_MetallicAtoms) then
350 loopStart = PREPAIR_LOOP
351 else
352 loopStart = PAIR_LOOP
353 endif
354
355 do loop = loopStart, loopEnd
356
357 ! See if we need to update neighbor lists
358 ! (but only on the first time through):
359 if (loop .eq. loopStart) then
360 #ifdef IS_MPI
361 call checkNeighborList(nGroupsInRow, q_group_row, skinThickness, &
362 update_nlist)
363 #else
364 call checkNeighborList(nGroups, q_group, skinThickness, &
365 update_nlist)
366 #endif
367 endif
368
369 if (update_nlist) then
370 !! save current configuration and construct neighbor list
371 #ifdef IS_MPI
372 call saveNeighborList(nGroupsInRow, q_group_row)
373 #else
374 call saveNeighborList(nGroups, q_group)
375 #endif
376 neighborListSize = size(list)
377 nlist = 0
378 endif
379
380 istart = 1
381 #ifdef IS_MPI
382 iend = nGroupsInRow
383 #else
384 iend = nGroups - 1
385 #endif
386 outer: do i = istart, iend
387
388 if (update_nlist) point(i) = nlist + 1
389
390 n_in_i = groupStartRow(i+1) - groupStartRow(i)
391
392 if (update_nlist) then
393 #ifdef IS_MPI
394 jstart = 1
395 jend = nGroupsInCol
396 #else
397 jstart = i+1
398 jend = nGroups
399 #endif
400 else
401 jstart = point(i)
402 jend = point(i+1) - 1
403 ! make sure group i has neighbors
404 if (jstart .gt. jend) cycle outer
405 endif
406
407 do jnab = jstart, jend
408 if (update_nlist) then
409 j = jnab
410 else
411 j = list(jnab)
412 endif
413
414 #ifdef IS_MPI
415 call get_interatomic_vector(q_group_Row(:,i), &
416 q_group_Col(:,j), d_grp, rgrpsq)
417 #else
418 call get_interatomic_vector(q_group(:,i), &
419 q_group(:,j), d_grp, rgrpsq)
420 #endif
421
422 if (rgrpsq < rListsq) then
423 if (update_nlist) then
424 nlist = nlist + 1
425
426 if (nlist > neighborListSize) then
427 #ifdef IS_MPI
428 call expandNeighborList(nGroupsInRow, listerror)
429 #else
430 call expandNeighborList(nGroups, listerror)
431 #endif
432 if (listerror /= 0) then
433 error = -1
434 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
435 return
436 end if
437 neighborListSize = size(list)
438 endif
439
440 list(nlist) = j
441 endif
442
443 if (rgrpsq < rCutsq) then
444
445 if (loop .eq. PAIR_LOOP) then
446 vij = 0.0_dp
447 fij(1) = 0.0_dp
448 fij(2) = 0.0_dp
449 fij(3) = 0.0_dp
450 endif
451
452 call get_switch(rgrpsq, sw, dswdr,rgrp, in_switching_region)
453
454 n_in_j = groupStartCol(j+1) - groupStartCol(j)
455
456 do ia = groupStartRow(i), groupStartRow(i+1)-1
457
458 atom1 = groupListRow(ia)
459
460 inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
461
462 atom2 = groupListCol(jb)
463
464 if (skipThisPair(atom1, atom2)) cycle inner
465
466 if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
467 d_atm(1) = d_grp(1)
468 d_atm(2) = d_grp(2)
469 d_atm(3) = d_grp(3)
470 ratmsq = rgrpsq
471 else
472 #ifdef IS_MPI
473 call get_interatomic_vector(q_Row(:,atom1), &
474 q_Col(:,atom2), d_atm, ratmsq)
475 #else
476 call get_interatomic_vector(q(:,atom1), &
477 q(:,atom2), d_atm, ratmsq)
478 #endif
479 endif
480
481 topoDist = getTopoDistance(atom1, atom2)
482
483 if (loop .eq. PREPAIR_LOOP) then
484 #ifdef IS_MPI
485 call f_do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
486 rgrpsq, d_grp, rCut, &
487 eFrame, A, f, t, pot_local)
488 #else
489 call f_do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
490 rgrpsq, d_grp, rCut, &
491 eFrame, A, f, t, pot)
492 #endif
493 else
494 #ifdef IS_MPI
495 call f_do_pair(atom1, atom2, ratmsq, d_atm, sw, &
496 eFrame, A, f, t, pot_local, particle_pot, vpair, &
497 fpair, d_grp, rgrp, rCut, topoDist)
498 ! particle_pot will be accumulated from row & column
499 ! arrays later
500 #else
501 call f_do_pair(atom1, atom2, ratmsq, d_atm, sw, &
502 eFrame, A, f, t, pot, particle_pot, vpair, &
503 fpair, d_grp, rgrp, rCut, topoDist)
504 #endif
505 vij = vij + vpair
506 fij(1) = fij(1) + fpair(1)
507 fij(2) = fij(2) + fpair(2)
508 fij(3) = fij(3) + fpair(3)
509 call add_stress_tensor(d_atm, fpair, tau)
510 endif
511 enddo inner
512 enddo
513
514 if (loop .eq. PAIR_LOOP) then
515 if (in_switching_region) then
516 swderiv = vij*dswdr/rgrp
517 fg = swderiv*d_grp
518
519 fij(1) = fij(1) + fg(1)
520 fij(2) = fij(2) + fg(2)
521 fij(3) = fij(3) + fg(3)
522
523 if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
524 call add_stress_tensor(d_atm, fg, tau)
525 endif
526
527 do ia=groupStartRow(i), groupStartRow(i+1)-1
528 atom1=groupListRow(ia)
529 mf = mfactRow(atom1)
530 ! fg is the force on atom ia due to cutoff group's
531 ! presence in switching region
532 fg = swderiv*d_grp*mf
533 #ifdef IS_MPI
534 f_Row(1,atom1) = f_Row(1,atom1) + fg(1)
535 f_Row(2,atom1) = f_Row(2,atom1) + fg(2)
536 f_Row(3,atom1) = f_Row(3,atom1) + fg(3)
537 #else
538 f(1,atom1) = f(1,atom1) + fg(1)
539 f(2,atom1) = f(2,atom1) + fg(2)
540 f(3,atom1) = f(3,atom1) + fg(3)
541 #endif
542 if (n_in_i .gt. 1) then
543 if (SIM_uses_AtomicVirial) then
544 ! find the distance between the atom
545 ! and the center of the cutoff group:
546 #ifdef IS_MPI
547 call get_interatomic_vector(q_Row(:,atom1), &
548 q_group_Row(:,i), dag, rag)
549 #else
550 call get_interatomic_vector(q(:,atom1), &
551 q_group(:,i), dag, rag)
552 #endif
553 call add_stress_tensor(dag,fg,tau)
554 endif
555 endif
556 enddo
557
558 do jb=groupStartCol(j), groupStartCol(j+1)-1
559 atom2=groupListCol(jb)
560 mf = mfactCol(atom2)
561 ! fg is the force on atom jb due to cutoff group's
562 ! presence in switching region
563 fg = -swderiv*d_grp*mf
564 #ifdef IS_MPI
565 f_Col(1,atom2) = f_Col(1,atom2) + fg(1)
566 f_Col(2,atom2) = f_Col(2,atom2) + fg(2)
567 f_Col(3,atom2) = f_Col(3,atom2) + fg(3)
568 #else
569 f(1,atom2) = f(1,atom2) + fg(1)
570 f(2,atom2) = f(2,atom2) + fg(2)
571 f(3,atom2) = f(3,atom2) + fg(3)
572 #endif
573 if (n_in_j .gt. 1) then
574 if (SIM_uses_AtomicVirial) then
575 ! find the distance between the atom
576 ! and the center of the cutoff group:
577 #ifdef IS_MPI
578 call get_interatomic_vector(q_Col(:,atom2), &
579 q_group_Col(:,j), dag, rag)
580 #else
581 call get_interatomic_vector(q(:,atom2), &
582 q_group(:,j), dag, rag)
583 #endif
584 call add_stress_tensor(dag,fg,tau)
585 endif
586 endif
587 enddo
588 endif
589 !if (.not.SIM_uses_AtomicVirial) then
590 ! call add_stress_tensor(d_grp, fij, tau)
591 !endif
592 endif
593 endif
594 endif
595 enddo
596
597 enddo outer
598
599 if (update_nlist) then
600 #ifdef IS_MPI
601 point(nGroupsInRow + 1) = nlist + 1
602 #else
603 point(nGroups) = nlist + 1
604 #endif
605 if (loop .eq. PREPAIR_LOOP) then
606 ! we just did the neighbor list update on the first
607 ! pass, so we don't need to do it
608 ! again on the second pass
609 update_nlist = .false.
610 endif
611 endif
612
613 if (loop .eq. PREPAIR_LOOP) then
614 #ifdef IS_MPI
615 call f_do_preforce(nlocal, pot_local, particle_pot)
616 #else
617 call f_do_preforce(nlocal, pot, particle_pot)
618 #endif
619 endif
620
621 enddo
622
623 !! Do timing
624 #ifdef PROFILE
625 call cpu_time(forceTimeFinal)
626 forceTime = forceTime + forceTimeFinal - forceTimeInitial
627 #endif
628
629 #ifdef IS_MPI
630 !!distribute forces
631
632 f_temp = 0.0_dp
633 call scatter(f_Row,f_temp,plan_atom_row_3d)
634 do i = 1,nlocal
635 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
636 end do
637
638 f_temp = 0.0_dp
639 call scatter(f_Col,f_temp,plan_atom_col_3d)
640 do i = 1,nlocal
641 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
642 end do
643
644 if (SIM_uses_DirectionalAtoms) then
645 t_temp = 0.0_dp
646 call scatter(t_Row,t_temp,plan_atom_row_3d)
647 do i = 1,nlocal
648 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
649 end do
650 t_temp = 0.0_dp
651 call scatter(t_Col,t_temp,plan_atom_col_3d)
652
653 do i = 1,nlocal
654 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
655 end do
656 endif
657
658 ! scatter/gather pot_row into the members of my column
659 do i = 1,LR_POT_TYPES
660 call scatter(pot_Row(i,:), pot_Temp(i,:), plan_atom_row)
661 end do
662 ! scatter/gather pot_local into all other procs
663 ! add resultant to get total pot
664 do i = 1, nlocal
665 pot_local(1:LR_POT_TYPES) = pot_local(1:LR_POT_TYPES) &
666 + pot_Temp(1:LR_POT_TYPES,i)
667 enddo
668
669 do i = 1,LR_POT_TYPES
670 particle_pot(1:nlocal) = particle_pot(1:nlocal) + pot_Temp(i,1:nlocal)
671 enddo
672
673 pot_Temp = 0.0_DP
674
675 do i = 1,LR_POT_TYPES
676 call scatter(pot_Col(i,:), pot_Temp(i,:), plan_atom_col)
677 end do
678
679 do i = 1, nlocal
680 pot_local(1:LR_POT_TYPES) = pot_local(1:LR_POT_TYPES)&
681 + pot_Temp(1:LR_POT_TYPES,i)
682 enddo
683
684 do i = 1,LR_POT_TYPES
685 particle_pot(1:nlocal) = particle_pot(1:nlocal) + pot_Temp(i,1:nlocal)
686 enddo
687
688 ppot_Temp = 0.0_DP
689
690 call scatter(ppot_Row(:), ppot_Temp(:), plan_atom_row)
691 do i = 1, nlocal
692 particle_pot(i) = particle_pot(i) + ppot_Temp(i)
693 enddo
694
695 ppot_Temp = 0.0_DP
696
697 call scatter(ppot_Col(:), ppot_Temp(:), plan_atom_col)
698 do i = 1, nlocal
699 particle_pot(i) = particle_pot(i) + ppot_Temp(i)
700 enddo
701
702 #endif
703
704 if (SIM_requires_skip_correction) then
705 do i = 1, nlocal
706
707 do i1 = 1, nSkipsForLocalAtom(i)
708 j = skipsForLocalAtom(i, i1)
709
710 ! prevent overcounting the skips
711 if (i.lt.j) then
712
713 call get_interatomic_vector(q(:,i), q(:,j), d_atm, ratmsq)
714 rVal = sqrt(ratmsq)
715 call get_switch(ratmsq, sw, dswdr, rVal,in_switching_region)
716 #ifdef IS_MPI
717 call do_skip_correction(c_idents_local(i), c_idents_local(j), &
718 d_atm, rVal, skipped_charge(i), skipped_charge(j), sw, &
719 1.0_dp, pot_local(ELECTROSTATIC_POT), vpair, f, t(:,i), t(:,j))
720 # else
721 call do_skip_correction(c_idents_local(i), c_idents_local(j), &
722 d_atm, rVal, skipped_charge(i), skipped_charge(j), sw, &
723 1.0_dp, pot(ELECTROSTATIC_POT), vpair, f, t(:,i), t(:,j))
724 #endif
725 endif
726 enddo
727 enddo
728 endif
729
730 if (SIM_requires_self_correction) then
731
732 do i = 1, nlocal
733
734 #ifdef IS_MPI
735 call do_self_correction(c_idents_local(i), eFrame(:,i), &
736 skipped_charge(i), pot_local(ELECTROSTATIC_POT), t(:,i))
737 #else
738 call do_self_correction(c_idents_local(i), eFrame(:,i), &
739 skipped_charge(i), pot(ELECTROSTATIC_POT), t(:,i))
740 #endif
741 enddo
742 endif
743
744 #ifdef IS_MPI
745 #ifdef SINGLE_PRECISION
746 call mpi_allreduce(pot_local, pot, LR_POT_TYPES,mpi_real,mpi_sum, &
747 mpi_comm_world,mpi_err)
748 #else
749 call mpi_allreduce(pot_local, pot, LR_POT_TYPES,mpi_double_precision, &
750 mpi_sum, mpi_comm_world,mpi_err)
751 #endif
752 #endif
753
754 end subroutine do_force_loop
755
756 subroutine f_do_pair(i, j, rijsq, d, sw, &
757 eFrame, A, f, t, pot, particle_pot, vpair, &
758 fpair, d_grp, r_grp, rCut, topoDist)
759
760 real( kind = dp ) :: vpair, sw
761 real( kind = dp ), dimension(LR_POT_TYPES) :: pot, pairpot
762 real( kind = dp ), dimension(nLocal) :: particle_pot
763 real( kind = dp ), dimension(3) :: fpair
764 real( kind = dp ), dimension(nLocal) :: mfact
765 real( kind = dp ), dimension(9,nLocal) :: eFrame
766 real( kind = dp ), dimension(9,nLocal) :: A
767 real( kind = dp ), dimension(3,nLocal) :: f
768 real( kind = dp ), dimension(3,nLocal) :: t
769
770 integer, intent(in) :: i, j
771 real ( kind = dp ), intent(inout) :: rijsq
772 real ( kind = dp ), intent(inout) :: r_grp
773 real ( kind = dp ), intent(inout) :: d(3)
774 real ( kind = dp ), intent(inout) :: d_grp(3)
775 real ( kind = dp ), intent(inout) :: rCut
776 integer, intent(inout) :: topoDist
777 real ( kind = dp ) :: r, pair_pot
778 real ( kind = dp ) :: a_k, b_k, c_k, d_k, dx
779
780 real( kind = dp), dimension(3) :: f1, t1, t2
781 real( kind = dp), dimension(9) :: A1, A2, eF1, eF2
782 real( kind = dp) :: dfrhodrho_i, dfrhodrho_j
783 real( kind = dp) :: rho_i, rho_j
784 real( kind = dp) :: fshift_i, fshift_j
785 real( kind = dp) :: p_vdw, p_elect, p_hb, p_met
786 integer :: id1, id2, idx
787 integer :: k
788 integer :: c_ident_i, c_ident_j
789
790 integer :: iHash
791
792 r = sqrt(rijsq)
793
794 vpair = 0.0_dp
795 fpair(1:3) = 0.0_dp
796
797 p_vdw = 0.0
798 p_elect = 0.0
799 p_hb = 0.0
800 p_met = 0.0
801
802 f1(1:3) = 0.0
803 t1(1:3) = 0.0
804 t2(1:3) = 0.0
805
806 #ifdef IS_MPI
807 c_ident_i = c_idents_row(i)
808 c_ident_j = c_idents_col(j)
809
810 A1(:) = A_Row(:,i)
811 A2(:) = A_Col(:,j)
812 eF1(:) = eFrame_Row(:,i)
813 eF2(:) = eFrame_Col(:,j)
814
815 dfrhodrho_i = dfrhodrho_row(i)
816 dfrhodrho_j = dfrhodrho_col(j)
817 rho_i = rho_row(i)
818 rho_j = rho_col(j)
819 #else
820 c_ident_i = c_idents_local(i)
821 c_ident_j = c_idents_local(j)
822
823 A1(:) = A(:,i)
824 A2(:) = A(:,j)
825 eF1(:) = eFrame(:,i)
826 eF2(:) = eFrame(:,j)
827
828 dfrhodrho_i = dfrhodrho(i)
829 dfrhodrho_j = dfrhodrho(j)
830 rho_i = rho(i)
831 rho_j = rho(j)
832 #endif
833
834 call do_pair(c_ident_i, c_ident_j, d, r, rijsq, sw, vpair, &
835 topoDist, A1, A2, eF1, eF2, &
836 pairpot, f1, t1, t2, &
837 rho_i, rho_j, dfrhodrho_i, dfrhodrho_j, fshift_i, fshift_j)
838
839 #ifdef IS_MPI
840 id1 = AtomRowToGlobal(i)
841 id2 = AtomColToGlobal(j)
842
843 pot_row(VDW_POT,i) = pot_row(VDW_POT,i) + 0.5*pairpot(VDW_POT)
844 pot_col(VDW_POT,j) = pot_col(VDW_POT,j) + 0.5*pairpot(VDW_POT)
845 pot_row(ELECTROSTATIC_POT,i) = pot_row(ELECTROSTATIC_POT,i) + 0.5*pairpot(ELECTROSTATIC_POT)
846 pot_col(ELECTROSTATIC_POT,j) = pot_col(ELECTROSTATIC_POT,j) + 0.5*pairpot(ELECTROSTATIC_POT)
847 pot_row(HB_POT,i) = pot_row(HB_POT,i) + 0.5*pairpot(HB_POT)
848 pot_col(HB_POT,j) = pot_col(HB_POT,j) + 0.5*pairpot(HB_POT)
849 pot_Row(METALLIC_POT,i) = pot_Row(METALLIC_POT,i) + 0.5*pairpot(METALLIC_POT)
850 pot_Col(METALLIC_POT,j) = pot_Col(METALLIC_POT,j) + 0.5*pairpot(METALLIC_POT)
851
852 do idx = 1, 3
853 f_Row(idx,i) = f_Row(idx,i) + f1(idx)
854 f_Col(idx,j) = f_Col(idx,j) - f1(idx)
855
856 t_Row(idx,i) = t_Row(idx,i) + t1(idx)
857 t_Col(idx,j) = t_Col(idx,j) + t2(idx)
858 enddo
859 ! particle_pot is the difference between the full potential
860 ! and the full potential without the presence of a particular
861 ! particle (atom1).
862 !
863 ! This reduces the density at other particle locations, so
864 ! we need to recompute the density at atom2 assuming atom1
865 ! didn't contribute. This then requires recomputing the
866 ! density functional for atom2 as well.
867 !
868 ! Most of the particle_pot heavy lifting comes from the
869 ! pair interaction, and will be handled by vpair. Parallel version.
870
871 if ( (iand(iHash, EAM_PAIR).ne.0) .or. (iand(iHash, SC_PAIR).ne.0) ) then
872 ppot_row(i) = ppot_row(i) - frho_row(j) + fshift_j
873 ppot_col(j) = ppot_col(j) - frho_col(i) + fshift_i
874 end if
875
876 #else
877 id1 = i
878 id2 = j
879
880 pot(VDW_POT) = pot(VDW_POT) + pairpot(VDW_POT)
881 pot(ELECTROSTATIC_POT) = pot(ELECTROSTATIC_POT) + pairpot(ELECTROSTATIC_POT)
882 pot(HB_POT) = pot(HB_POT) + pairpot(HB_POT)
883 pot(METALLIC_POT) = pot(METALLIC_POT) + pairpot(METALLIC_POT)
884
885 do idx = 1, 3
886 f(idx,i) = f(idx,i) + f1(idx)
887 f(idx,j) = f(idx,j) - f1(idx)
888
889 t(idx,i) = t(idx,i) + t1(idx)
890 t(idx,j) = t(idx,j) + t2(idx)
891 enddo
892 ! particle_pot is the difference between the full potential
893 ! and the full potential without the presence of a particular
894 ! particle (atom1).
895 !
896 ! This reduces the density at other particle locations, so
897 ! we need to recompute the density at atom2 assuming atom1
898 ! didn't contribute. This then requires recomputing the
899 ! density functional for atom2 as well.
900 !
901 ! Most of the particle_pot heavy lifting comes from the
902 ! pair interaction, and will be handled by vpair. NonParallel version.
903
904 if ( (iand(iHash, EAM_PAIR).ne.0) .or. (iand(iHash, SC_PAIR).ne.0) ) then
905 particle_pot(i) = particle_pot(i) - frho(j) + fshift_j
906 particle_pot(j) = particle_pot(j) - frho(i) + fshift_i
907 end if
908
909
910 #endif
911
912 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
913
914 fpair(1) = fpair(1) + f1(1)
915 fpair(2) = fpair(2) + f1(2)
916 fpair(3) = fpair(3) + f1(3)
917
918 endif
919 end subroutine f_do_pair
920
921 subroutine f_do_prepair(i, j, rijsq, d, sw, rcijsq, dc, rCut, &
922 eFrame, A, f, t, pot)
923
924 real( kind = dp ) :: sw
925 real( kind = dp ), dimension(LR_POT_TYPES) :: pot
926 real( kind = dp ), dimension(9,nLocal) :: eFrame
927 real (kind=dp), dimension(9,nLocal) :: A
928 real (kind=dp), dimension(3,nLocal) :: f
929 real (kind=dp), dimension(3,nLocal) :: t
930
931 integer, intent(in) :: i, j
932 real ( kind = dp ), intent(inout) :: rijsq, rcijsq, rCut
933 real ( kind = dp ) :: r, rc
934 real ( kind = dp ), intent(inout) :: d(3), dc(3)
935 real ( kind = dp ) :: rho_i_at_j, rho_j_at_i
936 integer :: c_ident_i, c_ident_j
937
938 r = sqrt(rijsq)
939
940 #ifdef IS_MPI
941 c_ident_i = c_idents_row(i)
942 c_ident_j = c_idents_col(j)
943 #else
944 c_ident_i = c_idents_local(i)
945 c_ident_j = c_idents_local(j)
946 #endif
947 rho_i_at_j = 0.0_dp
948 rho_j_at_i = 0.0_dp
949
950 call do_prepair(c_ident_i, c_ident_j, r, &
951 rho_i_at_j, rho_j_at_i)
952
953 #ifdef IS_MPI
954 rho_col(j) = rho_col(j) + rho_i_at_j
955 rho_row(i) = rho_row(i) + rho_j_at_i
956 #else
957 rho(j) = rho(j) + rho_i_at_j
958 rho(i) = rho(i) + rho_j_at_i
959 #endif
960
961 end subroutine f_do_prepair
962
963
964 subroutine f_do_preforce(nlocal, pot, particle_pot)
965 integer :: nlocal
966 real( kind = dp ),dimension(LR_POT_TYPES) :: pot
967 real( kind = dp ),dimension(nlocal) :: particle_pot
968 integer :: sc_err = 0
969 integer :: atom, c_ident1
970
971 if (SIM_uses_MetallicAtoms) then
972
973 #ifdef IS_MPI
974 call scatter(rho_row,rho,plan_atom_row,sc_err)
975 if (sc_err /= 0 ) then
976 call handleError("do_preforce()", "Error scattering rho_row into rho")
977 endif
978 call scatter(rho_col,rho_tmp,plan_atom_col,sc_err)
979 if (sc_err /= 0 ) then
980 call handleError("do_preforce()", "Error scattering rho_col into rho")
981 endif
982 rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
983 #endif
984
985
986 do atom = 1, nlocal
987 c_ident1 = c_idents_local(atom)
988
989 call do_preforce(c_ident1, rho(atom), frho(atom), dfrhodrho(atom))
990 pot(METALLIC_POT) = pot(METALLIC_POT) + frho(atom)
991 particle_pot(atom) = particle_pot(atom) + frho(atom)
992 end do
993
994 #ifdef IS_MPI
995 !! communicate f(rho) and derivatives back into row and column arrays
996 call gather(frho,frho_row,plan_atom_row, sc_err)
997 if (sc_err /= 0) then
998 call handleError("do_preforce()","MPI gather frho_row failure")
999 endif
1000 call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, sc_err)
1001 if (sc_err /= 0) then
1002 call handleError("do_preforce()","MPI gather dfrhodrho_row failure")
1003 endif
1004 call gather(frho,frho_col,plan_atom_col, sc_err)
1005 if (sc_err /= 0) then
1006 call handleError("do_preforce()","MPI gather frho_col failure")
1007 endif
1008 call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, sc_err)
1009 if (sc_err /= 0) then
1010 call handleError("do_preforce()","MPI gather dfrhodrho_col failure")
1011 endif
1012 #endif
1013
1014 end if
1015 end subroutine f_do_preforce
1016
1017
1018 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1019
1020 real(kind = dp), dimension(3) :: q_i
1021 real(kind = dp), dimension(3) :: q_j
1022 real(kind = dp), intent(out) :: r_sq
1023 real(kind = dp) :: d(3), scaled(3)
1024 real(kind = dp) :: t
1025 integer i
1026
1027 d(1) = q_j(1) - q_i(1)
1028 d(2) = q_j(2) - q_i(2)
1029 d(3) = q_j(3) - q_i(3)
1030
1031 ! Wrap back into periodic box if necessary
1032 if ( SIM_uses_PBC ) then
1033
1034 if( .not.boxIsOrthorhombic ) then
1035 ! calc the scaled coordinates.
1036 ! scaled = matmul(HmatInv, d)
1037 ! unwrap the matmul and do things explicitly:
1038
1039 scaled(1) = HmatInv(1,1)*d(1) + HmatInv(1,2)*d(2) + HmatInv(1,3)*d(3)
1040 scaled(2) = HmatInv(2,1)*d(1) + HmatInv(2,2)*d(2) + HmatInv(2,3)*d(3)
1041 scaled(3) = HmatInv(3,1)*d(1) + HmatInv(3,2)*d(2) + HmatInv(3,3)*d(3)
1042
1043 ! wrap the scaled coordinates (but don't use anint for speed)
1044
1045 t = scaled(1)
1046 if (t .ge. 0.0) then
1047 scaled(1) = t - floor(t + 0.5)
1048 else
1049 scaled(1) = t + ceiling(t - 0.5)
1050 endif
1051
1052 t = scaled(2)
1053 if (t .ge. 0.0) then
1054 scaled(2) = t - floor(t + 0.5)
1055 else
1056 scaled(2) = t + ceiling(t - 0.5)
1057 endif
1058
1059 t = scaled(3)
1060 if (t .ge. 0.0) then
1061 scaled(3) = t - floor(t + 0.5)
1062 else
1063 scaled(3) = t + ceiling(t - 0.5)
1064 endif
1065
1066 ! calc the wrapped real coordinates from the wrapped scaled
1067 ! coordinates
1068 ! d = matmul(Hmat,scaled)
1069 ! unwrap the matmul and do things explicitly:
1070
1071 d(1)= Hmat(1,1)*scaled(1) + Hmat(1,2)*scaled(2) + Hmat(1,3)*scaled(3)
1072 d(2)= Hmat(2,1)*scaled(1) + Hmat(2,2)*scaled(2) + Hmat(2,3)*scaled(3)
1073 d(3)= Hmat(3,1)*scaled(1) + Hmat(3,2)*scaled(2) + Hmat(3,3)*scaled(3)
1074
1075 else
1076 ! calc the scaled coordinates.
1077
1078 scaled(1) = d(1) * HmatInv(1,1)
1079 scaled(2) = d(2) * HmatInv(2,2)
1080 scaled(3) = d(3) * HmatInv(3,3)
1081
1082 ! wrap the scaled coordinates (but don't use anint for speed)
1083
1084 t = scaled(1)
1085 if (t .ge. 0.0) then
1086 scaled(1) = t - floor(t + 0.5)
1087 else
1088 scaled(1) = t + ceiling(t - 0.5)
1089 endif
1090
1091 t = scaled(2)
1092 if (t .ge. 0.0) then
1093 scaled(2) = t - floor(t + 0.5)
1094 else
1095 scaled(2) = t + ceiling(t - 0.5)
1096 endif
1097
1098 t = scaled(3)
1099 if (t .ge. 0.0) then
1100 scaled(3) = t - floor(t + 0.5)
1101 else
1102 scaled(3) = t + ceiling(t - 0.5)
1103 endif
1104
1105 ! calc the wrapped real coordinates from the wrapped scaled
1106 ! coordinates
1107
1108 d(1) = scaled(1)*Hmat(1,1)
1109 d(2) = scaled(2)*Hmat(2,2)
1110 d(3) = scaled(3)*Hmat(3,3)
1111
1112 endif
1113
1114 endif
1115
1116 r_sq = d(1)*d(1) + d(2)*d(2) + d(3)*d(3)
1117
1118 end subroutine get_interatomic_vector
1119
1120 subroutine zero_work_arrays()
1121
1122 #ifdef IS_MPI
1123
1124 q_Row = 0.0_dp
1125 q_Col = 0.0_dp
1126
1127 q_group_Row = 0.0_dp
1128 q_group_Col = 0.0_dp
1129
1130 eFrame_Row = 0.0_dp
1131 eFrame_Col = 0.0_dp
1132
1133 A_Row = 0.0_dp
1134 A_Col = 0.0_dp
1135
1136 f_Row = 0.0_dp
1137 f_Col = 0.0_dp
1138 f_Temp = 0.0_dp
1139
1140 t_Row = 0.0_dp
1141 t_Col = 0.0_dp
1142 t_Temp = 0.0_dp
1143
1144 pot_Row = 0.0_dp
1145 pot_Col = 0.0_dp
1146 pot_Temp = 0.0_dp
1147 ppot_Temp = 0.0_dp
1148
1149 frho_row = 0.0_dp
1150 frho_col = 0.0_dp
1151 rho_row = 0.0_dp
1152 rho_col = 0.0_dp
1153 rho_tmp = 0.0_dp
1154 dfrhodrho_row = 0.0_dp
1155 dfrhodrho_col = 0.0_dp
1156
1157 #endif
1158 rho = 0.0_dp
1159 frho = 0.0_dp
1160 dfrhodrho = 0.0_dp
1161
1162 end subroutine zero_work_arrays
1163
1164 function skipThisPair(atom1, atom2) result(skip_it)
1165 integer, intent(in) :: atom1
1166 integer, intent(in), optional :: atom2
1167 logical :: skip_it
1168 integer :: unique_id_1, unique_id_2
1169 integer :: i
1170
1171 skip_it = .false.
1172
1173 !! there are a number of reasons to skip a pair or a particle
1174 !! mostly we do this to exclude atoms who are involved in short
1175 !! range interactions (bonds, bends, torsions), but we also need
1176 !! to exclude some overcounted interactions that result from
1177 !! the parallel decomposition
1178
1179 #ifdef IS_MPI
1180 !! in MPI, we have to look up the unique IDs for each atom
1181 unique_id_1 = AtomRowToGlobal(atom1)
1182 unique_id_2 = AtomColToGlobal(atom2)
1183 !! this situation should only arise in MPI simulations
1184 if (unique_id_1 == unique_id_2) then
1185 skip_it = .true.
1186 return
1187 end if
1188
1189 !! this prevents us from doing the pair on multiple processors
1190 if (unique_id_1 < unique_id_2) then
1191 if (mod(unique_id_1 + unique_id_2,2) == 0) then
1192 skip_it = .true.
1193 return
1194 endif
1195 else
1196 if (mod(unique_id_1 + unique_id_2,2) == 1) then
1197 skip_it = .true.
1198 return
1199 endif
1200 endif
1201 #else
1202 !! in the normal loop, the atom numbers are unique
1203 unique_id_1 = atom1
1204 unique_id_2 = atom2
1205 #endif
1206
1207 #ifdef IS_MPI
1208 do i = 1, nSkipsForRowAtom(atom1)
1209 if (skipsForRowAtom(atom1, i) .eq. unique_id_2) then
1210 skip_it = .true.
1211 return
1212 endif
1213 end do
1214 #else
1215 do i = 1, nSkipsForLocalAtom(atom1)
1216 if (skipsForLocalAtom(atom1, i) .eq. unique_id_2) then
1217 skip_it = .true.
1218 return
1219 endif
1220 end do
1221 #endif
1222
1223 return
1224 end function skipThisPair
1225
1226 function getTopoDistance(atom1, atom2) result(topoDist)
1227 integer, intent(in) :: atom1
1228 integer, intent(in) :: atom2
1229 integer :: topoDist
1230 integer :: unique_id_2
1231 integer :: i
1232
1233 #ifdef IS_MPI
1234 unique_id_2 = AtomColToGlobal(atom2)
1235 #else
1236 unique_id_2 = atom2
1237 #endif
1238
1239 ! zero is default for unconnected (i.e. normal) pair interactions
1240
1241 topoDist = 0
1242
1243 do i = 1, nTopoPairsForAtom(atom1)
1244 if (toposForAtom(atom1, i) .eq. unique_id_2) then
1245 topoDist = topoDistance(atom1, i)
1246 return
1247 endif
1248 end do
1249
1250 return
1251 end function getTopoDistance
1252
1253 #ifdef PROFILE
1254 function getforcetime() result(totalforcetime)
1255 real(kind=dp) :: totalforcetime
1256 totalforcetime = forcetime
1257 end function getforcetime
1258 #endif
1259
1260 !! This cleans componets of force arrays belonging only to fortran
1261
1262 subroutine add_stress_tensor(dpair, fpair, tau)
1263
1264 real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1265 real( kind = dp ), dimension(9), intent(inout) :: tau
1266
1267 ! because the d vector is the rj - ri vector, and
1268 ! because fx, fy, fz are the force on atom i, we need a
1269 ! negative sign here:
1270
1271 tau(1) = tau(1) - dpair(1) * fpair(1)
1272 tau(2) = tau(2) - dpair(1) * fpair(2)
1273 tau(3) = tau(3) - dpair(1) * fpair(3)
1274 tau(4) = tau(4) - dpair(2) * fpair(1)
1275 tau(5) = tau(5) - dpair(2) * fpair(2)
1276 tau(6) = tau(6) - dpair(2) * fpair(3)
1277 tau(7) = tau(7) - dpair(3) * fpair(1)
1278 tau(8) = tau(8) - dpair(3) * fpair(2)
1279 tau(9) = tau(9) - dpair(3) * fpair(3)
1280
1281 end subroutine add_stress_tensor
1282
1283 end module doForces

Properties

Name Value
svn:keywords Author Id Revision Date