ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
Revision: 843
Committed: Wed Oct 29 20:41:39 2003 UTC (20 years, 8 months ago) by mmeineke
File size: 29972 byte(s)
Log Message:
fixed a stdlib.h include error in bass.l

fixed a little bug in the first time step, regarding the setting of ecr and est in fortran

File Contents

# User Rev Content
1 mmeineke 377 !! do_Forces.F90
2     !! module do_Forces
3     !! Calculates Long Range forces.
4    
5     !! @author Charles F. Vardeman II
6     !! @author Matthew Meineke
7 mmeineke 843 !! @version $Id: do_Forces.F90,v 1.35 2003-10-29 20:41:39 mmeineke Exp $, $Date: 2003-10-29 20:41:39 $, $Name: not supported by cvs2svn $, $Revision: 1.35 $
8 mmeineke 377
9     module do_Forces
10     use force_globals
11     use simulation
12     use definitions
13     use atype_module
14     use neighborLists
15     use lj
16     use sticky_pair
17     use dipole_dipole
18     use reaction_field
19     use gb_pair
20 mmeineke 626 use vector_class
21 chuckv 650 use eam
22 chuckv 657 use status
23 mmeineke 377 #ifdef IS_MPI
24     use mpiSimulation
25     #endif
26    
27     implicit none
28     PRIVATE
29    
30     #define __FORTRAN90
31     #include "fForceField.h"
32    
33 mmeineke 626 logical, save :: do_forces_initialized = .false., haveRlist = .false.
34     logical, save :: havePolicies = .false.
35 mmeineke 377 logical, save :: FF_uses_LJ
36     logical, save :: FF_uses_sticky
37     logical, save :: FF_uses_dipoles
38     logical, save :: FF_uses_RF
39     logical, save :: FF_uses_GB
40     logical, save :: FF_uses_EAM
41    
42 mmeineke 626 real(kind=dp), save :: rlist, rlistsq
43    
44 mmeineke 377 public :: init_FF
45     public :: do_force_loop
46 mmeineke 626 public :: setRlistDF
47 mmeineke 377
48 chuckv 694 #ifdef PROFILE
49     real(kind = dp) :: forceTime
50     real(kind = dp) :: forceTimeInitial, forceTimeFinal
51     real(kind = dp) :: globalForceTime
52     real(kind = dp) :: maxForceTime
53     integer, save :: nloops = 0
54     #endif
55    
56 mmeineke 377 contains
57    
58 mmeineke 626 subroutine setRlistDF( this_rlist )
59    
60     real(kind=dp) :: this_rlist
61    
62     rlist = this_rlist
63     rlistsq = rlist * rlist
64    
65     haveRlist = .true.
66     if( havePolicies ) do_forces_initialized = .true.
67    
68     end subroutine setRlistDF
69    
70 mmeineke 377 subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
71    
72     integer, intent(in) :: LJMIXPOLICY
73     logical, intent(in) :: use_RF_c
74    
75     integer, intent(out) :: thisStat
76     integer :: my_status, nMatches
77     integer, pointer :: MatchList(:) => null()
78     real(kind=dp) :: rcut, rrf, rt, dielect
79    
80     !! assume things are copacetic, unless they aren't
81     thisStat = 0
82    
83     !! Fortran's version of a cast:
84     FF_uses_RF = use_RF_c
85    
86     !! init_FF is called *after* all of the atom types have been
87     !! defined in atype_module using the new_atype subroutine.
88     !!
89     !! this will scan through the known atypes and figure out what
90     !! interactions are used by the force field.
91    
92     FF_uses_LJ = .false.
93     FF_uses_sticky = .false.
94     FF_uses_dipoles = .false.
95     FF_uses_GB = .false.
96     FF_uses_EAM = .false.
97    
98     call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
99     if (nMatches .gt. 0) FF_uses_LJ = .true.
100    
101     call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
102     if (nMatches .gt. 0) FF_uses_dipoles = .true.
103    
104     call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
105     MatchList)
106     if (nMatches .gt. 0) FF_uses_Sticky = .true.
107    
108     call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
109     if (nMatches .gt. 0) FF_uses_GB = .true.
110    
111     call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
112     if (nMatches .gt. 0) FF_uses_EAM = .true.
113    
114     !! check to make sure the FF_uses_RF setting makes sense
115    
116     if (FF_uses_dipoles) then
117     if (FF_uses_RF) then
118     dielect = getDielect()
119 mmeineke 626 call initialize_rf(dielect)
120 mmeineke 377 endif
121     else
122     if (FF_uses_RF) then
123     write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
124     thisStat = -1
125     return
126     endif
127 mmeineke 626 endif
128 mmeineke 377
129     if (FF_uses_LJ) then
130    
131     select case (LJMIXPOLICY)
132 gezelter 834 case (LB_MIXING_RULE)
133     call init_lj_FF(LB_MIXING_RULE, my_status)
134     case (EXPLICIT_MIXING_RULE)
135     call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
136 mmeineke 377 case default
137     write(default_error,*) 'unknown LJ Mixing Policy!'
138     thisStat = -1
139     return
140     end select
141     if (my_status /= 0) then
142     thisStat = -1
143     return
144     end if
145     endif
146    
147     if (FF_uses_sticky) then
148     call check_sticky_FF(my_status)
149     if (my_status /= 0) then
150     thisStat = -1
151     return
152     end if
153     endif
154 chuckv 657
155    
156     if (FF_uses_EAM) then
157 chuckv 801 call init_EAM_FF(my_status)
158 chuckv 657 if (my_status /= 0) then
159 chuckv 801 write(*,*) "init_EAM_FF returned a bad status"
160 chuckv 657 thisStat = -1
161     return
162     end if
163     endif
164    
165    
166 mmeineke 377
167     if (FF_uses_GB) then
168     call check_gb_pair_FF(my_status)
169     if (my_status .ne. 0) then
170     thisStat = -1
171     return
172     endif
173     endif
174    
175     if (FF_uses_GB .and. FF_uses_LJ) then
176     endif
177 chuckv 480 if (.not. do_forces_initialized) then
178     !! Create neighbor lists
179     call expandNeighborList(getNlocal(), my_status)
180     if (my_Status /= 0) then
181     write(default_error,*) "SimSetup: ExpandNeighborList returned error."
182     thisStat = -1
183     return
184     endif
185     endif
186 chuckv 657
187 mmeineke 377
188 mmeineke 626 havePolicies = .true.
189     if( haveRlist ) do_forces_initialized = .true.
190 chuckv 657
191 mmeineke 377 end subroutine init_FF
192    
193    
194     !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
195     !------------------------------------------------------------->
196     subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
197     error)
198     !! Position array provided by C, dimensioned by getNlocal
199     real ( kind = dp ), dimension(3,getNlocal()) :: q
200     !! Rotation Matrix for each long range particle in simulation.
201     real( kind = dp), dimension(9,getNlocal()) :: A
202     !! Unit vectors for dipoles (lab frame)
203     real( kind = dp ), dimension(3,getNlocal()) :: u_l
204     !! Force array provided by C, dimensioned by getNlocal
205     real ( kind = dp ), dimension(3,getNlocal()) :: f
206     !! Torsion array provided by C, dimensioned by getNlocal
207     real( kind = dp ), dimension(3,getNlocal()) :: t
208     !! Stress Tensor
209     real( kind = dp), dimension(9) :: tau
210     real ( kind = dp ) :: pot
211     logical ( kind = 2) :: do_pot_c, do_stress_c
212     logical :: do_pot
213     logical :: do_stress
214 chuckv 439 #ifdef IS_MPI
215 chuckv 441 real( kind = DP ) :: pot_local
216 mmeineke 377 integer :: nrow
217     integer :: ncol
218 chuckv 694 integer :: nprocs
219 mmeineke 377 #endif
220     integer :: nlocal
221     integer :: natoms
222     logical :: update_nlist
223     integer :: i, j, jbeg, jend, jnab
224     integer :: nlist
225 mmeineke 626 real( kind = DP ) :: rijsq
226 mmeineke 377 real(kind=dp),dimension(3) :: d
227     real(kind=dp) :: rfpot, mu_i, virial
228     integer :: me_i
229     logical :: is_dp_i
230     integer :: neighborListSize
231     integer :: listerror, error
232     integer :: localError
233 mmeineke 626
234     real(kind=dp) :: listSkin = 1.0
235 mmeineke 619
236 mmeineke 377
237     !! initialize local variables
238    
239     #ifdef IS_MPI
240 chuckv 441 pot_local = 0.0_dp
241 mmeineke 377 nlocal = getNlocal()
242     nrow = getNrow(plan_row)
243     ncol = getNcol(plan_col)
244     #else
245     nlocal = getNlocal()
246     natoms = nlocal
247     #endif
248 chuckv 669
249 mmeineke 377 call check_initialization(localError)
250     if ( localError .ne. 0 ) then
251 chuckv 657 call handleError("do_force_loop","Not Initialized")
252 mmeineke 377 error = -1
253     return
254     end if
255     call zero_work_arrays()
256    
257     do_pot = do_pot_c
258     do_stress = do_stress_c
259    
260 chuckv 669
261 mmeineke 377 ! Gather all information needed by all force loops:
262    
263     #ifdef IS_MPI
264    
265     call gather(q,q_Row,plan_row3d)
266     call gather(q,q_Col,plan_col3d)
267    
268     if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
269     call gather(u_l,u_l_Row,plan_row3d)
270     call gather(u_l,u_l_Col,plan_col3d)
271    
272     call gather(A,A_Row,plan_row_rotation)
273     call gather(A,A_Col,plan_col_rotation)
274     endif
275    
276     #endif
277 chuckv 694
278     !! Begin force loop timing:
279     #ifdef PROFILE
280     call cpu_time(forceTimeInitial)
281     nloops = nloops + 1
282     #endif
283 chuckv 669
284 mmeineke 377 if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
285     !! See if we need to update neighbor lists
286 mmeineke 626 call checkNeighborList(nlocal, q, listSkin, update_nlist)
287 mmeineke 377 !! if_mpi_gather_stuff_for_prepair
288     !! do_prepair_loop_if_needed
289     !! if_mpi_scatter_stuff_from_prepair
290     !! if_mpi_gather_stuff_from_prepair_to_main_loop
291 chuckv 673
292 chuckv 648 !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
293     #ifdef IS_MPI
294    
295     if (update_nlist) then
296    
297     !! save current configuration, construct neighbor list,
298     !! and calculate forces
299     call saveNeighborList(nlocal, q)
300    
301     neighborListSize = size(list)
302     nlist = 0
303    
304     do i = 1, nrow
305     point(i) = nlist + 1
306    
307     prepair_inner: do j = 1, ncol
308    
309     if (skipThisPair(i,j)) cycle prepair_inner
310    
311     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
312    
313     if (rijsq < rlistsq) then
314    
315     nlist = nlist + 1
316    
317     if (nlist > neighborListSize) then
318     call expandNeighborList(nlocal, listerror)
319     if (listerror /= 0) then
320     error = -1
321     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
322     return
323     end if
324     neighborListSize = size(list)
325     endif
326    
327     list(nlist) = j
328     call do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot_local)
329     endif
330     enddo prepair_inner
331     enddo
332    
333     point(nrow + 1) = nlist + 1
334    
335     else !! (of update_check)
336    
337     ! use the list to find the neighbors
338     do i = 1, nrow
339     JBEG = POINT(i)
340     JEND = POINT(i+1) - 1
341     ! check thiat molecule i has neighbors
342     if (jbeg .le. jend) then
343    
344     do jnab = jbeg, jend
345     j = list(jnab)
346    
347     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
348     call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
349     u_l, A, f, t, pot_local)
350    
351     enddo
352     endif
353     enddo
354     endif
355    
356     #else
357    
358     if (update_nlist) then
359    
360     ! save current configuration, contruct neighbor list,
361     ! and calculate forces
362     call saveNeighborList(natoms, q)
363    
364     neighborListSize = size(list)
365    
366     nlist = 0
367 chuckv 673
368 chuckv 648 do i = 1, natoms-1
369     point(i) = nlist + 1
370    
371     prepair_inner: do j = i+1, natoms
372    
373     if (skipThisPair(i,j)) cycle prepair_inner
374    
375     call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
376    
377    
378     if (rijsq < rlistsq) then
379 chuckv 673
380    
381 chuckv 648 nlist = nlist + 1
382    
383     if (nlist > neighborListSize) then
384     call expandNeighborList(natoms, listerror)
385     if (listerror /= 0) then
386     error = -1
387     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
388     return
389     end if
390     neighborListSize = size(list)
391     endif
392    
393     list(nlist) = j
394    
395     call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
396     u_l, A, f, t, pot)
397    
398     endif
399     enddo prepair_inner
400     enddo
401    
402     point(natoms) = nlist + 1
403    
404     else !! (update)
405 chuckv 673
406 chuckv 648 ! use the list to find the neighbors
407     do i = 1, natoms-1
408     JBEG = POINT(i)
409     JEND = POINT(i+1) - 1
410     ! check thiat molecule i has neighbors
411     if (jbeg .le. jend) then
412    
413     do jnab = jbeg, jend
414     j = list(jnab)
415    
416     call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
417     call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
418     u_l, A, f, t, pot)
419    
420     enddo
421     endif
422     enddo
423     endif
424     #endif
425     !! Do rest of preforce calculations
426 chuckv 673 !! do necessary preforce calculations
427     call do_preforce(nlocal,pot)
428     ! we have already updated the neighbor list set it to false...
429     update_nlist = .false.
430 mmeineke 377 else
431 chuckv 648 !! See if we need to update neighbor lists for non pre-pair
432 mmeineke 626 call checkNeighborList(nlocal, q, listSkin, update_nlist)
433 mmeineke 377 endif
434 chuckv 648
435    
436    
437    
438    
439     !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>>>>>>>>>>>>>>>>
440    
441    
442    
443    
444    
445 mmeineke 377 #ifdef IS_MPI
446    
447     if (update_nlist) then
448    
449     !! save current configuration, construct neighbor list,
450     !! and calculate forces
451 mmeineke 459 call saveNeighborList(nlocal, q)
452 mmeineke 377
453     neighborListSize = size(list)
454     nlist = 0
455    
456     do i = 1, nrow
457     point(i) = nlist + 1
458    
459     inner: do j = 1, ncol
460    
461     if (skipThisPair(i,j)) cycle inner
462    
463     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
464    
465 mmeineke 626 if (rijsq < rlistsq) then
466 mmeineke 377
467     nlist = nlist + 1
468    
469     if (nlist > neighborListSize) then
470     call expandNeighborList(nlocal, listerror)
471     if (listerror /= 0) then
472     error = -1
473     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
474     return
475     end if
476     neighborListSize = size(list)
477     endif
478    
479     list(nlist) = j
480    
481 mmeineke 626 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
482     u_l, A, f, t, pot_local)
483    
484 mmeineke 377 endif
485     enddo inner
486     enddo
487    
488     point(nrow + 1) = nlist + 1
489    
490     else !! (of update_check)
491    
492     ! use the list to find the neighbors
493     do i = 1, nrow
494     JBEG = POINT(i)
495     JEND = POINT(i+1) - 1
496     ! check thiat molecule i has neighbors
497     if (jbeg .le. jend) then
498    
499     do jnab = jbeg, jend
500     j = list(jnab)
501    
502     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
503     call do_pair(i, j, rijsq, d, do_pot, do_stress, &
504 chuckv 441 u_l, A, f, t, pot_local)
505 mmeineke 377
506     enddo
507     endif
508     enddo
509     endif
510    
511     #else
512    
513     if (update_nlist) then
514    
515     ! save current configuration, contruct neighbor list,
516     ! and calculate forces
517 mmeineke 459 call saveNeighborList(natoms, q)
518 mmeineke 377
519     neighborListSize = size(list)
520    
521     nlist = 0
522    
523     do i = 1, natoms-1
524     point(i) = nlist + 1
525    
526     inner: do j = i+1, natoms
527    
528 chuckv 388 if (skipThisPair(i,j)) cycle inner
529    
530 mmeineke 377 call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
531    
532 chuckv 388
533 mmeineke 626 if (rijsq < rlistsq) then
534 mmeineke 377
535     nlist = nlist + 1
536    
537     if (nlist > neighborListSize) then
538     call expandNeighborList(natoms, listerror)
539     if (listerror /= 0) then
540     error = -1
541     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
542     return
543     end if
544     neighborListSize = size(list)
545     endif
546    
547     list(nlist) = j
548    
549 mmeineke 626 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
550 chuckv 441 u_l, A, f, t, pot)
551 mmeineke 626
552 mmeineke 377 endif
553     enddo inner
554     enddo
555    
556     point(natoms) = nlist + 1
557    
558     else !! (update)
559    
560     ! use the list to find the neighbors
561     do i = 1, natoms-1
562     JBEG = POINT(i)
563     JEND = POINT(i+1) - 1
564     ! check thiat molecule i has neighbors
565     if (jbeg .le. jend) then
566    
567     do jnab = jbeg, jend
568     j = list(jnab)
569    
570     call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
571     call do_pair(i, j, rijsq, d, do_pot, do_stress, &
572 chuckv 441 u_l, A, f, t, pot)
573 mmeineke 377
574     enddo
575     endif
576     enddo
577     endif
578    
579     #endif
580    
581     ! phew, done with main loop.
582 chuckv 694
583     !! Do timing
584     #ifdef PROFILE
585     call cpu_time(forceTimeFinal)
586     forceTime = forceTime + forceTimeFinal - forceTimeInitial
587     #endif
588    
589    
590 mmeineke 377 #ifdef IS_MPI
591     !!distribute forces
592 chuckv 438
593     f_temp = 0.0_dp
594     call scatter(f_Row,f_temp,plan_row3d)
595     do i = 1,nlocal
596     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
597     end do
598    
599     f_temp = 0.0_dp
600 mmeineke 377 call scatter(f_Col,f_temp,plan_col3d)
601     do i = 1,nlocal
602     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
603     end do
604    
605     if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
606 chuckv 438 t_temp = 0.0_dp
607     call scatter(t_Row,t_temp,plan_row3d)
608     do i = 1,nlocal
609     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
610     end do
611     t_temp = 0.0_dp
612 mmeineke 377 call scatter(t_Col,t_temp,plan_col3d)
613    
614     do i = 1,nlocal
615     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
616     end do
617     endif
618    
619     if (do_pot) then
620     ! scatter/gather pot_row into the members of my column
621     call scatter(pot_Row, pot_Temp, plan_row)
622 chuckv 439
623 mmeineke 377 ! scatter/gather pot_local into all other procs
624     ! add resultant to get total pot
625     do i = 1, nlocal
626     pot_local = pot_local + pot_Temp(i)
627     enddo
628 chuckv 439
629     pot_Temp = 0.0_DP
630 mmeineke 377
631     call scatter(pot_Col, pot_Temp, plan_col)
632     do i = 1, nlocal
633     pot_local = pot_local + pot_Temp(i)
634     enddo
635 chuckv 439
636 mmeineke 377 endif
637     #endif
638    
639     if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
640    
641     if (FF_uses_RF .and. SimUsesRF()) then
642    
643     #ifdef IS_MPI
644     call scatter(rf_Row,rf,plan_row3d)
645     call scatter(rf_Col,rf_Temp,plan_col3d)
646     do i = 1,nlocal
647     rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
648     end do
649     #endif
650    
651     do i = 1, getNlocal()
652    
653     rfpot = 0.0_DP
654     #ifdef IS_MPI
655     me_i = atid_row(i)
656     #else
657     me_i = atid(i)
658     #endif
659     call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
660     if ( is_DP_i ) then
661     call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
662     !! The reaction field needs to include a self contribution
663     !! to the field:
664     call accumulate_self_rf(i, mu_i, u_l)
665     !! Get the reaction field contribution to the
666     !! potential and torques:
667     call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
668     #ifdef IS_MPI
669     pot_local = pot_local + rfpot
670     #else
671     pot = pot + rfpot
672    
673     #endif
674     endif
675     enddo
676     endif
677     endif
678    
679    
680     #ifdef IS_MPI
681    
682     if (do_pot) then
683 chuckv 441 pot = pot + pot_local
684 mmeineke 377 !! we assume the c code will do the allreduce to get the total potential
685     !! we could do it right here if we needed to...
686     endif
687    
688     if (do_stress) then
689 gezelter 490 call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
690 mmeineke 377 mpi_comm_world,mpi_err)
691 chuckv 470 call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
692 mmeineke 377 mpi_comm_world,mpi_err)
693     endif
694    
695     #else
696    
697     if (do_stress) then
698     tau = tau_Temp
699     virial = virial_Temp
700     endif
701    
702     #endif
703 chuckv 694
704     #ifdef PROFILE
705     if (do_pot) then
706    
707     #ifdef IS_MPI
708    
709    
710     call printCommTime()
711    
712     call mpi_allreduce(forceTime,globalForceTime,1,MPI_DOUBLE_PRECISION, &
713     mpi_sum,mpi_comm_world,mpi_err)
714    
715     call mpi_allreduce(forceTime,maxForceTime,1,MPI_DOUBLE_PRECISION, &
716     MPI_MAX,mpi_comm_world,mpi_err)
717    
718     call mpi_comm_size( MPI_COMM_WORLD, nprocs,mpi_err)
719    
720     if (getMyNode() == 0) then
721     write(*,*) "Total processor time spent in force calculations is: ", globalForceTime
722     write(*,*) "Total Time spent in force loop per processor is: ", globalforceTime/nprocs
723     write(*,*) "Maximum force time on any processor is: ", maxForceTime
724     end if
725     #else
726     write(*,*) "Time spent in force loop is: ", forceTime
727     #endif
728    
729    
730     endif
731    
732     #endif
733    
734 mmeineke 377 end subroutine do_force_loop
735    
736 chuckv 441 subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
737 mmeineke 377
738     real( kind = dp ) :: pot
739 chuckv 460 real( kind = dp ), dimension(3,getNlocal()) :: u_l
740     real (kind=dp), dimension(9,getNlocal()) :: A
741     real (kind=dp), dimension(3,getNlocal()) :: f
742     real (kind=dp), dimension(3,getNlocal()) :: t
743 mmeineke 377
744     logical, intent(inout) :: do_pot, do_stress
745     integer, intent(in) :: i, j
746     real ( kind = dp ), intent(inout) :: rijsq
747     real ( kind = dp ) :: r
748     real ( kind = dp ), intent(inout) :: d(3)
749     logical :: is_LJ_i, is_LJ_j
750     logical :: is_DP_i, is_DP_j
751     logical :: is_GB_i, is_GB_j
752 chuckv 648 logical :: is_EAM_i,is_EAM_j
753 mmeineke 377 logical :: is_Sticky_i, is_Sticky_j
754     integer :: me_i, me_j
755    
756     r = sqrt(rijsq)
757    
758     #ifdef IS_MPI
759 gezelter 490 if (tagRow(i) .eq. tagColumn(j)) then
760     write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
761     endif
762 mmeineke 377
763     me_i = atid_row(i)
764     me_j = atid_col(j)
765    
766     #else
767    
768     me_i = atid(i)
769     me_j = atid(j)
770    
771     #endif
772    
773     if (FF_uses_LJ .and. SimUsesLJ()) then
774     call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
775     call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
776    
777     if ( is_LJ_i .and. is_LJ_j ) &
778     call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
779     endif
780    
781     if (FF_uses_dipoles .and. SimUsesDipoles()) then
782     call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
783     call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
784    
785     if ( is_DP_i .and. is_DP_j ) then
786 gezelter 462 call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
787 mmeineke 377 do_pot, do_stress)
788     if (FF_uses_RF .and. SimUsesRF()) then
789     call accumulate_rf(i, j, r, u_l)
790     call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
791     endif
792    
793     endif
794     endif
795    
796     if (FF_uses_Sticky .and. SimUsesSticky()) then
797    
798     call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
799     call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
800 chuckv 388
801 mmeineke 377 if ( is_Sticky_i .and. is_Sticky_j ) then
802     call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
803     do_pot, do_stress)
804     endif
805     endif
806    
807    
808     if (FF_uses_GB .and. SimUsesGB()) then
809    
810 tim 726
811 mmeineke 377 call getElementProperty(atypes, me_i, "is_GB", is_GB_i)
812     call getElementProperty(atypes, me_j, "is_GB", is_GB_j)
813    
814     if ( is_GB_i .and. is_GB_j ) then
815     call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
816     do_pot, do_stress)
817     endif
818     endif
819    
820 mmeineke 597
821 chuckv 648
822     if (FF_uses_EAM .and. SimUsesEAM()) then
823     call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
824     call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
825    
826     if ( is_EAM_i .and. is_EAM_j ) &
827     call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
828     endif
829    
830 mmeineke 597
831 chuckv 648
832    
833 mmeineke 377 end subroutine do_pair
834    
835    
836 chuckv 631
837 chuckv 648 subroutine do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
838 chuckv 631 real( kind = dp ) :: pot
839     real( kind = dp ), dimension(3,getNlocal()) :: u_l
840     real (kind=dp), dimension(9,getNlocal()) :: A
841     real (kind=dp), dimension(3,getNlocal()) :: f
842     real (kind=dp), dimension(3,getNlocal()) :: t
843    
844     logical, intent(inout) :: do_pot, do_stress
845     integer, intent(in) :: i, j
846     real ( kind = dp ), intent(inout) :: rijsq
847     real ( kind = dp ) :: r
848     real ( kind = dp ), intent(inout) :: d(3)
849    
850     logical :: is_EAM_i, is_EAM_j
851    
852     integer :: me_i, me_j
853    
854     r = sqrt(rijsq)
855    
856 chuckv 669
857 chuckv 631 #ifdef IS_MPI
858     if (tagRow(i) .eq. tagColumn(j)) then
859     write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
860     endif
861    
862     me_i = atid_row(i)
863     me_j = atid_col(j)
864    
865     #else
866    
867     me_i = atid(i)
868     me_j = atid(j)
869    
870     #endif
871 chuckv 673
872 chuckv 631 if (FF_uses_EAM .and. SimUsesEAM()) then
873     call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
874     call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
875    
876 chuckv 648 if ( is_EAM_i .and. is_EAM_j ) &
877     call calc_EAM_prepair_rho(i, j, d, r, rijsq )
878 chuckv 631 endif
879 chuckv 648
880 chuckv 673 end subroutine do_prepair
881 chuckv 648
882    
883    
884 chuckv 673
885 chuckv 648 subroutine do_preforce(nlocal,pot)
886     integer :: nlocal
887     real( kind = dp ) :: pot
888    
889 chuckv 669 if (FF_uses_EAM .and. SimUsesEAM()) then
890     call calc_EAM_preforce_Frho(nlocal,pot)
891     endif
892 chuckv 648
893    
894 chuckv 631 end subroutine do_preforce
895    
896    
897 mmeineke 377 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
898    
899     real (kind = dp), dimension(3) :: q_i
900     real (kind = dp), dimension(3) :: q_j
901     real ( kind = dp ), intent(out) :: r_sq
902 gezelter 571 real( kind = dp ) :: d(3), scaled(3)
903     integer i
904    
905 chuckv 482 d(1:3) = q_j(1:3) - q_i(1:3)
906 gezelter 571
907 mmeineke 377 ! Wrap back into periodic box if necessary
908     if ( SimUsesPBC() ) then
909 mmeineke 393
910 gezelter 571 if( .not.boxIsOrthorhombic ) then
911     ! calc the scaled coordinates.
912    
913 mmeineke 572 scaled = matmul(HmatInv, d)
914 gezelter 571
915     ! wrap the scaled coordinates
916    
917 mmeineke 572 scaled = scaled - anint(scaled)
918    
919 gezelter 571
920     ! calc the wrapped real coordinates from the wrapped scaled
921     ! coordinates
922    
923 mmeineke 572 d = matmul(Hmat,scaled)
924 gezelter 571
925     else
926     ! calc the scaled coordinates.
927    
928     do i = 1, 3
929     scaled(i) = d(i) * HmatInv(i,i)
930    
931     ! wrap the scaled coordinates
932    
933     scaled(i) = scaled(i) - anint(scaled(i))
934    
935     ! calc the wrapped real coordinates from the wrapped scaled
936     ! coordinates
937    
938     d(i) = scaled(i)*Hmat(i,i)
939     enddo
940     endif
941 mmeineke 393
942 mmeineke 377 endif
943 gezelter 571
944 mmeineke 377 r_sq = dot_product(d,d)
945 gezelter 571
946 mmeineke 377 end subroutine get_interatomic_vector
947 gezelter 571
948 mmeineke 377 subroutine check_initialization(error)
949     integer, intent(out) :: error
950    
951     error = 0
952     ! Make sure we are properly initialized.
953     if (.not. do_forces_initialized) then
954 chuckv 657 write(*,*) "Forces not initialized"
955 mmeineke 377 error = -1
956     return
957     endif
958    
959     #ifdef IS_MPI
960     if (.not. isMPISimSet()) then
961     write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
962     error = -1
963     return
964     endif
965     #endif
966    
967     return
968     end subroutine check_initialization
969    
970    
971     subroutine zero_work_arrays()
972    
973     #ifdef IS_MPI
974    
975     q_Row = 0.0_dp
976     q_Col = 0.0_dp
977    
978     u_l_Row = 0.0_dp
979     u_l_Col = 0.0_dp
980    
981     A_Row = 0.0_dp
982     A_Col = 0.0_dp
983    
984     f_Row = 0.0_dp
985     f_Col = 0.0_dp
986     f_Temp = 0.0_dp
987    
988     t_Row = 0.0_dp
989     t_Col = 0.0_dp
990     t_Temp = 0.0_dp
991    
992     pot_Row = 0.0_dp
993     pot_Col = 0.0_dp
994     pot_Temp = 0.0_dp
995    
996     rf_Row = 0.0_dp
997     rf_Col = 0.0_dp
998     rf_Temp = 0.0_dp
999    
1000     #endif
1001    
1002 chuckv 673
1003     if (FF_uses_EAM .and. SimUsesEAM()) then
1004     call clean_EAM()
1005     endif
1006    
1007    
1008    
1009    
1010    
1011 mmeineke 377 rf = 0.0_dp
1012     tau_Temp = 0.0_dp
1013     virial_Temp = 0.0_dp
1014     end subroutine zero_work_arrays
1015    
1016     function skipThisPair(atom1, atom2) result(skip_it)
1017     integer, intent(in) :: atom1
1018     integer, intent(in), optional :: atom2
1019     logical :: skip_it
1020     integer :: unique_id_1, unique_id_2
1021 chuckv 388 integer :: me_i,me_j
1022 mmeineke 377 integer :: i
1023    
1024     skip_it = .false.
1025    
1026     !! there are a number of reasons to skip a pair or a particle
1027     !! mostly we do this to exclude atoms who are involved in short
1028     !! range interactions (bonds, bends, torsions), but we also need
1029     !! to exclude some overcounted interactions that result from
1030     !! the parallel decomposition
1031    
1032     #ifdef IS_MPI
1033     !! in MPI, we have to look up the unique IDs for each atom
1034     unique_id_1 = tagRow(atom1)
1035     #else
1036     !! in the normal loop, the atom numbers are unique
1037     unique_id_1 = atom1
1038     #endif
1039 chuckv 388
1040 mmeineke 377 !! We were called with only one atom, so just check the global exclude
1041     !! list for this atom
1042     if (.not. present(atom2)) then
1043     do i = 1, nExcludes_global
1044     if (excludesGlobal(i) == unique_id_1) then
1045     skip_it = .true.
1046     return
1047     end if
1048     end do
1049     return
1050     end if
1051    
1052     #ifdef IS_MPI
1053     unique_id_2 = tagColumn(atom2)
1054     #else
1055     unique_id_2 = atom2
1056     #endif
1057 chuckv 441
1058 mmeineke 377 #ifdef IS_MPI
1059     !! this situation should only arise in MPI simulations
1060     if (unique_id_1 == unique_id_2) then
1061     skip_it = .true.
1062     return
1063     end if
1064    
1065     !! this prevents us from doing the pair on multiple processors
1066     if (unique_id_1 < unique_id_2) then
1067 chuckv 441 if (mod(unique_id_1 + unique_id_2,2) == 0) then
1068     skip_it = .true.
1069     return
1070     endif
1071 mmeineke 377 else
1072 chuckv 441 if (mod(unique_id_1 + unique_id_2,2) == 1) then
1073     skip_it = .true.
1074     return
1075     endif
1076 mmeineke 377 endif
1077     #endif
1078 chuckv 441
1079 mmeineke 377 !! the rest of these situations can happen in all simulations:
1080     do i = 1, nExcludes_global
1081     if ((excludesGlobal(i) == unique_id_1) .or. &
1082     (excludesGlobal(i) == unique_id_2)) then
1083     skip_it = .true.
1084     return
1085     endif
1086     enddo
1087 chuckv 441
1088 mmeineke 377 do i = 1, nExcludes_local
1089     if (excludesLocal(1,i) == unique_id_1) then
1090     if (excludesLocal(2,i) == unique_id_2) then
1091     skip_it = .true.
1092     return
1093     endif
1094     else
1095     if (excludesLocal(1,i) == unique_id_2) then
1096     if (excludesLocal(2,i) == unique_id_1) then
1097     skip_it = .true.
1098     return
1099     endif
1100     endif
1101     endif
1102     end do
1103    
1104     return
1105     end function skipThisPair
1106    
1107     function FF_UsesDirectionalAtoms() result(doesit)
1108     logical :: doesit
1109     doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1110     FF_uses_GB .or. FF_uses_RF
1111     end function FF_UsesDirectionalAtoms
1112    
1113     function FF_RequiresPrepairCalc() result(doesit)
1114     logical :: doesit
1115     doesit = FF_uses_EAM
1116     end function FF_RequiresPrepairCalc
1117    
1118     function FF_RequiresPostpairCalc() result(doesit)
1119     logical :: doesit
1120     doesit = FF_uses_RF
1121     end function FF_RequiresPostpairCalc
1122    
1123 chuckv 673 !! This cleans componets of force arrays belonging only to fortran
1124    
1125 mmeineke 377 end module do_Forces