ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
Revision: 295
Committed: Thu Mar 6 19:57:03 2003 UTC (21 years, 4 months ago) by chuckv
File size: 19996 byte(s)
Log Message:
Split force loop into subroutines. Moved wrap out of simulation module.

File Contents

# Content
1 !! Calculates Long Range forces.
2 !! @author Charles F. Vardeman II
3 !! @author Matthew Meineke
4 !! @version $Id: do_Forces.F90,v 1.3 2003-03-06 19:57:03 chuckv Exp $, $Date: 2003-03-06 19:57:03 $, $Name: not supported by cvs2svn $, $Revision: 1.3 $
5
6
7
8 module do_Forces
9 use simulation
10 use definitions
11 use generic_atypes
12 use neighborLists
13
14 use lj_FF
15 use sticky_FF
16 use dp_FF
17 use gb_FF
18
19 #ifdef IS_MPI
20 use mpiSimulation
21 #endif
22 implicit none
23 PRIVATE
24
25 !! Number of lj_atypes in lj_atype_list
26 integer, save :: n_atypes = 0
27
28 !! Global list of lj atypes in simulation
29 type (atype), pointer :: ListHead => null()
30 type (atype), pointer :: ListTail => null()
31
32
33
34
35 logical, save :: firstTime = .True.
36
37 !! Atype identity pointer lists
38 #ifdef IS_MPI
39 !! Row lj_atype pointer list
40 type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
41 !! Column lj_atype pointer list
42 type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
43 #else
44 type(identPtrList ), dimension(:), pointer :: identPtrList => null()
45 #endif
46
47
48 !! Logical has lj force field module been initialized?
49 logical, save :: isFFinit = .false.
50
51 !! Use periodic boundry conditions
52 logical :: wrap = .false.
53
54 !! Potential energy global module variables
55 #ifdef IS_MPI
56 real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
57 real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
58
59 real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
60 real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
61
62 real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
63 real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
64
65 real(kind = dp), dimension(3,getNrow(plan_row)) :: ARow = 0.0_dp
66 real(kind = dp), dimension(3,getNcol(plan_col)) :: ACol = 0.0_dp
67
68
69
70 real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
71 real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
72
73
74 real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
75 real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
76
77
78
79 real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
80 real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
81
82 real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
83 #endif
84 real(kind = dp) :: pe = 0.0_dp
85 real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
86 real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
87 real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
88
89 logical :: do_preForce = .false.
90 logical :: do_postForce = .false.
91
92
93
94 !! Public methods and data
95 public :: new_atype
96 public :: do_forceLoop
97 public :: init_FF
98
99
100
101
102 contains
103
104 !! Adds a new lj_atype to the list.
105 subroutine new_atype(ident,mass,epsilon,sigma, &
106 is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
107 real( kind = dp ), intent(in) :: mass
108 real( kind = dp ), intent(in) :: epsilon
109 real( kind = dp ), intent(in) :: sigma
110 real( kind = dp ), intent(in) :: w0
111 real( kind = dp ), intent(in) :: v0
112 real( kind = dp ), intent(in) :: dipoleMoment
113
114 integer, intent(in) :: ident
115 integer, intent(out) :: status
116 integer, intent(in) :: is_Sticky
117 integer, intent(in) :: is_DP
118 integer, intent(in) :: is_GB
119 integer, intent(in) :: is_LJ
120
121
122 type (atype), pointer :: the_new_atype
123 integer :: alloc_error
124 integer :: atype_counter = 0
125 integer :: alloc_size
126 integer :: err_stat
127 status = 0
128
129
130
131 ! allocate a new atype
132 allocate(the_new_atype,stat=alloc_error)
133 if (alloc_error /= 0 ) then
134 status = -1
135 return
136 end if
137
138 ! assign our new atype information
139 the_new_atype%mass = mass
140 the_new_atype%epsilon = epsilon
141 the_new_atype%sigma = sigma
142 the_new_atype%sigma2 = sigma * sigma
143 the_new_atype%sigma6 = the_new_atype%sigma2 * the_new_atype%sigma2 &
144 * the_new_atype%sigma2
145 the_new_atype%w0 = w0
146 the_new_atype%v0 = v0
147 the_new_atype%dipoleMoment = dipoleMoment
148
149
150 ! assume that this atype will be successfully added
151 the_new_atype%atype_ident = ident
152 the_new_atype%atype_number = n_lj_atypes + 1
153
154 if ( is_Sticky /= 0 ) the_new_atype%is_Sticky = .true.
155 if ( is_GB /= 0 ) the_new_atype%is_GB = .true.
156 if ( is_LJ /= 0 ) the_new_atype%is_LJ = .true.
157 if ( is_DP /= 0 ) the_new_atype%is_DP = .true.
158
159 call add_atype(the_new_atype,ListHead,ListTail,err_stat)
160 if (err_stat /= 0 ) then
161 status = -1
162 return
163 endif
164
165 n_atypes = n_atypes + 1
166
167
168 end subroutine new_atype
169
170
171 subroutine init_FF(nComponents,ident, status)
172 !! Number of components in ident array
173 integer, intent(inout) :: nComponents
174 !! Array of identities nComponents long corresponding to
175 !! ljatype ident.
176 integer, dimension(nComponents),intent(inout) :: ident
177 !! Result status, success = 0, error = -1
178 integer, intent(out) :: Status
179
180 integer :: alloc_stat
181
182 integer :: thisStat
183 integer :: i
184
185 integer :: myNode
186 #ifdef IS_MPI
187 integer, allocatable, dimension(:) :: identRow
188 integer, allocatable, dimension(:) :: identCol
189 integer :: nrow
190 integer :: ncol
191 #endif
192 status = 0
193
194
195
196
197 !! if were're not in MPI, we just update ljatypePtrList
198 #ifndef IS_MPI
199 call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
200 if ( thisStat /= 0 ) then
201 status = -1
202 return
203 endif
204
205
206 ! if were're in MPI, we also have to worry about row and col lists
207 #else
208
209 ! We can only set up forces if mpiSimulation has been setup.
210 if (.not. isMPISimSet()) then
211 write(default_error,*) "MPI is not set"
212 status = -1
213 return
214 endif
215 nrow = getNrow(plan_row)
216 ncol = getNcol(plan_col)
217 mynode = getMyNode()
218 !! Allocate temperary arrays to hold gather information
219 allocate(identRow(nrow),stat=alloc_stat)
220 if (alloc_stat /= 0 ) then
221 status = -1
222 return
223 endif
224
225 allocate(identCol(ncol),stat=alloc_stat)
226 if (alloc_stat /= 0 ) then
227 status = -1
228 return
229 endif
230
231 !! Gather idents into row and column idents
232
233 call gather(ident,identRow,plan_row)
234 call gather(ident,identCol,plan_col)
235
236
237 !! Create row and col pointer lists
238
239 call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
240 if (thisStat /= 0 ) then
241 status = -1
242 return
243 endif
244
245 call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
246 if (thisStat /= 0 ) then
247 status = -1
248 return
249 endif
250
251 !! free temporary ident arrays
252 if (allocated(identCol)) then
253 deallocate(identCol)
254 end if
255 if (allocated(identCol)) then
256 deallocate(identRow)
257 endif
258
259 #endif
260
261 call initForce_Modules(thisStat)
262 if (thisStat /= 0) then
263 status = -1
264 return
265 endif
266
267 !! Create neighbor lists
268 call expandList(thisStat)
269 if (thisStat /= 0) then
270 status = -1
271 return
272 endif
273
274 isFFinit = .true.
275
276
277 end subroutine init_FF
278
279
280
281
282 subroutine initForce_Modules(thisStat)
283 integer, intent(out) :: thisStat
284 integer :: my_status
285
286 thisStat = 0
287 call init_lj_FF(ListHead,my_status)
288 if (my_status /= 0) then
289 thisStat = -1
290 return
291 end if
292
293 end subroutine initForce_Modules
294
295
296
297
298 !! FORCE routine Calculates Lennard Jones forces.
299 !------------------------------------------------------------->
300 subroutine do__force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
301 !! Position array provided by C, dimensioned by getNlocal
302 real ( kind = dp ), dimension(3,getNlocal()) :: q
303 !! Rotation Matrix for each long range particle in simulation.
304 real( kind = dp), dimension(9,getNlocal()) :: A
305
306 !! Magnitude dipole moment
307 real( kind = dp ), dimension(3,getNlocal()) :: mu
308 !! Unit vectors for dipoles (lab frame)
309 real( kind = dp ), dimension(3,getNlocal()) :: u_l
310 !! Force array provided by C, dimensioned by getNlocal
311 real ( kind = dp ), dimension(3,getNlocal()) :: f
312 !! Torsion array provided by C, dimensioned by getNlocal
313 real( kind = dp ), dimension(3,getNlocal()) :: t
314
315 !! Stress Tensor
316 real( kind = dp), dimension(9) :: tau
317
318 real ( kind = dp ) :: potE
319 logical ( kind = 2) :: do_pot
320 integer :: FFerror
321
322
323 type(atype), pointer :: Atype_i
324 type(atype), pointer :: Atype_j
325
326
327
328
329
330
331 #ifdef IS_MPI
332 real( kind = DP ) :: pot_local
333
334 !! Local arrays needed for MPI
335
336 #endif
337
338
339
340 real( kind = DP ) :: pe
341 logical :: update_nlist
342
343
344 integer :: i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
345 integer :: nlist
346 integer :: j_start
347
348 real( kind = DP ) :: r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
349
350 real( kind = DP ) :: rx_ij, ry_ij, rz_ij, rijsq
351 real( kind = DP ) :: rlistsq, rcutsq,rlist,rcut
352
353 real( kind = DP ) :: dielectric = 0.0_dp
354
355 ! a rig that need to be fixed.
356 #ifdef IS_MPI
357 real( kind = dp ) :: pe_local
358 integer :: nlocal
359 #endif
360 integer :: nrow
361 integer :: ncol
362 integer :: natoms
363 integer :: neighborListSize
364 integer :: listerror
365 !! should we calculate the stress tensor
366 logical :: do_stress = .false.
367
368
369 FFerror = 0
370
371 ! Make sure we are properly initialized.
372 if (.not. isFFInit) then
373 write(default_error,*) "ERROR: lj_FF has not been properly initialized"
374 FFerror = -1
375 return
376 endif
377 #ifdef IS_MPI
378 if (.not. isMPISimSet()) then
379 write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
380 FFerror = -1
381 return
382 endif
383 #endif
384
385 !! initialize local variables
386 natoms = getNlocal()
387 call getRcut(rcut,rcut2=rcutsq)
388 call getRlist(rlist,rlistsq)
389
390 !! Find ensemble
391 if (isEnsemble("NPT")) do_stress = .true.
392 !! set to wrap
393 if (isPBC()) wrap = .true.
394
395
396 #ifndef IS_MPI
397 nrow = natoms - 1
398 ncol = natoms
399 #else
400 nrow = getNrow(plan_row)
401 ncol = getNcol(plan_col)
402 nlocal = natoms
403 j_start = 1
404 #endif
405
406
407 !! See if we need to update neighbor lists
408 call check(q,update_nlist)
409
410 !--------------WARNING...........................
411 ! Zero variables, NOTE:::: Forces are zeroed in C
412 ! Zeroing them here could delete previously computed
413 ! Forces.
414 !------------------------------------------------
415 call zero_module_variables()
416
417
418 ! communicate MPI positions
419 #ifdef IS_MPI
420 call gather(q,qRow,plan_row3d)
421 call gather(q,qCol,plan_col3d)
422
423 call gather(mu,muRow,plan_row3d)
424 call gather(mu,muCol,plan_col3d)
425
426 call gather(u_l,u_lRow,plan_row3d)
427 call gather(u_l,u_lCol,plan_col3d)
428
429 call gather(A,ARow,plan_row_rotation)
430 call gather(A,ACol,plan_col_rotation)
431 #endif
432
433
434 if (update_nlist) then
435
436 ! save current configuration, contruct neighbor list,
437 ! and calculate forces
438 call save_neighborList(q)
439
440 neighborListSize = getNeighborListSize()
441 nlist = 0
442
443
444
445 do i = 1, nrow
446 point(i) = nlist + 1
447 #ifdef IS_MPI
448 Atype_i => identPtrListRow(i)%this
449 tag_i = tagRow(i)
450 #else
451 Atype_i => identPtrList(i)%this
452 j_start = i + 1
453 #endif
454
455 inner: do j = j_start, ncol
456 ! Assign identity pointers and tags
457 #ifdef IS_MPI
458 Atype_j => identPtrListColumn(j)%this
459
460 call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
461 rxij,ryij,rzij,rijsq,r)
462 !! For mpi, use newtons 3rd law when building neigbor list
463 !! Also check to see the particle i != j.
464 if (mpi_cycle_jLoop(i,j)) cycle inner:
465
466 #else
467 Atype_j => identPtrList(j)%this
468 call get_interatomic_vector(i,j,q(:,i),q(:,j),&
469 rxij,ryij,rzij,rijsq,r)
470
471 #endif
472
473 if (rijsq < rlistsq) then
474
475 nlist = nlist + 1
476
477 if (nlist > neighborListSize) then
478 call expandList(listerror)
479 if (listerror /= 0) then
480 FFerror = -1
481 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
482 return
483 end if
484 endif
485
486 list(nlist) = j
487
488
489 if (rijsq < rcutsq) then
490 call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
491 endif
492 enddo inner
493 enddo
494
495 #ifdef IS_MPI
496 point(nrow + 1) = nlist + 1
497 #else
498 point(natoms) = nlist + 1
499 #endif
500
501 else !! (update)
502
503 ! use the list to find the neighbors
504 do i = 1, nrow
505 JBEG = POINT(i)
506 JEND = POINT(i+1) - 1
507 ! check thiat molecule i has neighbors
508 if (jbeg .le. jend) then
509
510 #ifdef IS_MPI
511 ljAtype_i => identPtrListRow(i)%this
512 #else
513 ljAtype_i => identPtrList(i)%this
514 #endif
515 do jnab = jbeg, jend
516 j = list(jnab)
517 #ifdef IS_MPI
518 ljAtype_j = identPtrListColumn(j)%this
519 call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
520 rxij,ryij,rzij,rijsq,r)
521
522 #else
523 ljAtype_j = identPtrList(j)%this
524 call get_interatomic_vector(i,j,q(:,i),q(:,j),&
525 rxij,ryij,rzij,rijsq,r)
526 #endif
527 call do_pair(i,j,r,rxij,ryij,rzij)
528 enddo
529 endif
530 enddo
531 endif
532
533
534
535 #ifdef IS_MPI
536 !!distribute forces
537
538 call scatter(fRow,f,plan_row3d)
539 call scatter(fCol,fTemp,plan_col3d)
540
541 do i = 1,nlocal
542 f(1:3,i) = f(1:3,i) + fTemp(1:3,i)
543 end do
544
545 if (do_torque) then
546 call scatter(tRow,t,plan_row3d)
547 call scatter(tCol,tTemp,plan_col3d)
548
549 do i = 1,nlocal
550 t(1:3,i) = t(1:3,i) + tTemp(1:3,i)
551 end do
552 endif
553
554 if (do_pot) then
555 ! scatter/gather pot_row into the members of my column
556 call scatter(eRow,eTemp,plan_row)
557
558 ! scatter/gather pot_local into all other procs
559 ! add resultant to get total pot
560 do i = 1, nlocal
561 pe_local = pe_local + eTemp(i)
562 enddo
563
564 eTemp = 0.0E0_DP
565 call scatter(eCol,eTemp,plan_col)
566 do i = 1, nlocal
567 pe_local = pe_local + eTemp(i)
568 enddo
569
570 pe = pe_local
571 endif
572 #else
573 ! Copy local array into return array for c
574 f = fTemp
575 t = tTemp
576 #endif
577
578 potE = pe
579
580
581 if (do_stress) then
582 #ifdef IS_MPI
583 mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
584 mpi_comm_world,mpi_err)
585 #else
586 tau = tauTemp
587 #endif
588 endif
589
590 end subroutine do_force_loop
591
592
593
594
595
596
597
598
599
600
601 !! Calculate any pre-force loop components and update nlist if necessary.
602 subroutine do_preForce(updateNlist)
603 logical, intent(inout) :: updateNlist
604
605
606
607 end subroutine do_preForce
608
609
610
611
612
613
614
615
616
617
618
619
620
621 !! Calculate any post force loop components, i.e. reaction field, etc.
622 subroutine do_postForce()
623
624
625
626 end subroutine do_postForce
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644 subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
645 type (atype ), pointer, intent(inout) :: atype_i
646 type (atype ), pointer, intent(inout) :: atype_j
647 integer :: i
648 integer :: j
649 real ( kind = dp ), intent(inout) :: rx_ij
650 real ( kind = dp ), intent(inout) :: ry_ij
651 real ( kind = dp ), intent(inout) :: rz_ij
652
653
654 real( kind = dp ) :: fx = 0.0_dp
655 real( kind = dp ) :: fy = 0.0_dp
656 real( kind = dp ) :: fz = 0.0_dp
657
658 real( kind = dp ) :: drdx = 0.0_dp
659 real( kind = dp ) :: drdy = 0.0_dp
660 real( kind = dp ) :: drdz = 0.0_dp
661
662
663
664
665
666
667 call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j)
668
669 #ifdef IS_MPI
670 eRow(i) = eRow(i) + pot*0.5
671 eCol(i) = eCol(i) + pot*0.5
672 #else
673 pe = pe + pot
674 #endif
675
676 drdx = -rxij / r
677 drdy = -ryij / r
678 drdz = -rzij / r
679
680 fx = dudr * drdx
681 fy = dudr * drdy
682 fz = dudr * drdz
683
684
685
686
687
688
689
690 #ifdef IS_MPI
691 fCol(1,j) = fCol(1,j) - fx
692 fCol(2,j) = fCol(2,j) - fy
693 fCol(3,j) = fCol(3,j) - fz
694
695 fRow(1,j) = fRow(1,j) + fx
696 fRow(2,j) = fRow(2,j) + fy
697 fRow(3,j) = fRow(3,j) + fz
698 #else
699 fTemp(1,j) = fTemp(1,j) - fx
700 fTemp(2,j) = fTemp(2,j) - fy
701 fTemp(3,j) = fTemp(3,j) - fz
702 fTemp(1,i) = fTemp(1,i) + fx
703 fTemp(2,i) = fTemp(2,i) + fy
704 fTemp(3,i) = fTemp(3,i) + fz
705 #endif
706
707 if (do_stress) then
708 tauTemp(1) = tauTemp(1) + fx * rxij
709 tauTemp(2) = tauTemp(2) + fx * ryij
710 tauTemp(3) = tauTemp(3) + fx * rzij
711 tauTemp(4) = tauTemp(4) + fy * rxij
712 tauTemp(5) = tauTemp(5) + fy * ryij
713 tauTemp(6) = tauTemp(6) + fy * rzij
714 tauTemp(7) = tauTemp(7) + fz * rxij
715 tauTemp(8) = tauTemp(8) + fz * ryij
716 tauTemp(9) = tauTemp(9) + fz * rzij
717 endif
718
719
720
721 end subroutine do_pair
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738 subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
739 !---------------- Arguments-------------------------------
740 !! index i
741
742 !! Position array
743 real (kind = dp), dimension(3) :: q_i
744 real (kind = dp), dimension(3) :: q_j
745 !! x component of vector between i and j
746 real ( kind = dp ), intent(out) :: rx_ij
747 !! y component of vector between i and j
748 real ( kind = dp ), intent(out) :: ry_ij
749 !! z component of vector between i and j
750 real ( kind = dp ), intent(out) :: rz_ij
751 !! magnitude of r squared
752 real ( kind = dp ), intent(out) :: r_sq
753 !! magnitude of vector r between atoms i and j.
754 real ( kind = dp ), intent(out) :: r_ij
755 !! wrap into periodic box.
756 logical, intent(in) :: wrap
757
758 !--------------- Local Variables---------------------------
759 !! Distance between i and j
760 real( kind = dp ) :: d(3)
761 !---------------- END DECLARATIONS-------------------------
762
763
764 ! Find distance between i and j
765 d(1:3) = q_i(1:3) - q_j(1:3)
766
767 ! Wrap back into periodic box if necessary
768 if ( wrap ) then
769 d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
770 int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
771 end if
772
773 ! Find Magnitude of the vector
774 r_sq = dot_product(d,d)
775 r_ij = sqrt(r_sq)
776
777 ! Set each component for force calculation
778 rx_ij = d(1)
779 ry_ij = d(2)
780 rz_ij = d(3)
781
782
783 end subroutine get_interatomic_vector
784
785 subroutine zero_module_variables()
786
787 #ifndef IS_MPI
788
789 pe = 0.0E0_DP
790 tauTemp = 0.0_dp
791 fTemp = 0.0_dp
792 tTemp = 0.0_dp
793 #else
794 qRow = 0.0_dp
795 qCol = 0.0_dp
796
797 muRow = 0.0_dp
798 muCol = 0.0_dp
799
800 u_lRow = 0.0_dp
801 u_lCol = 0.0_dp
802
803 ARow = 0.0_dp
804 ACol = 0.0_dp
805
806 fRow = 0.0_dp
807 fCol = 0.0_dp
808
809
810 tRow = 0.0_dp
811 tCol = 0.0_dp
812
813
814
815 eRow = 0.0_dp
816 eCol = 0.0_dp
817 eTemp = 0.0_dp
818 #endif
819
820 end subroutine zero_module_variables
821
822 #ifdef IS_MPI
823 !! Function to properly build neighbor lists in MPI using newtons 3rd law.
824 !! We don't want 2 processors doing the same i j pair twice.
825 !! Also checks to see if i and j are the same particle.
826 function mpi_cycle_jLoop(i,j) result(do_cycle)
827 !--------------- Arguments--------------------------
828 ! Index i
829 integer,intent(in) :: i
830 ! Index j
831 integer,intent(in) :: j
832 ! Result do_cycle
833 logical :: do_cycle
834 !--------------- Local variables--------------------
835 integer :: tag_i
836 integer :: tag_j
837 !--------------- END DECLARATIONS------------------
838 tag_i = tagRow(i)
839 tag_j = tagColumn(j)
840
841 do_cycle = .false.
842
843 if (tag_i == tag_j) then
844 do_cycle = .true.
845 return
846 end if
847
848 if (tag_i < tag_j) then
849 if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
850 return
851 else
852 if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
853 endif
854 end function mpi_cycle_jLoop
855 #endif
856
857 end module do_Forces