ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE/libmdtools/do_Forces.F90 (file contents):
Revision 1144 by tim, Sat May 1 18:52:38 2004 UTC vs.
Revision 1214 by gezelter, Tue Jun 1 18:42:58 2004 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.53 2004-05-01 18:52:38 tim Exp $, $Date: 2004-05-01 18:52:38 $, $Name: not supported by cvs2svn $, $Revision: 1.53 $
7 > !! @version $Id: do_Forces.F90,v 1.67 2004-06-01 18:42:58 gezelter Exp $, $Date: 2004-06-01 18:42:58 $, $Name: not supported by cvs2svn $, $Revision: 1.67 $
8  
9   module do_Forces
10    use force_globals
11    use simulation
12    use definitions
13    use atype_module
14 +  use switcheroo
15    use neighborLists  
16    use lj
17    use sticky_pair
# Line 30 | Line 31 | module do_Forces
31  
32   #define __FORTRAN90
33   #include "fForceField.h"
34 + #include "fSwitchingFunction.h"
35  
36 +  INTEGER, PARAMETER:: PREPAIR_LOOP = 1
37 +  INTEGER, PARAMETER:: PAIR_LOOP    = 2
38 +
39    logical, save :: haveRlist = .false.
40    logical, save :: haveNeighborList = .false.
41    logical, save :: havePolicies = .false.
# Line 62 | Line 67 | module do_Forces
67    public :: init_FF
68    public :: do_force_loop
69    public :: setRlistDF
65
70  
71   #ifdef PROFILE
72    public :: getforcetime
# Line 279 | Line 283 | contains
283      
284      !! Assume sanity (for the sake of argument)
285      haveSaneForceField = .true.
282    !!
283    if (FF_uses_charges) then
284      dielect = getDielect()
285      call initialize_charge(dielect)
286    endif
286  
288
287      !! check to make sure the FF_uses_RF setting makes sense
288      
289      if (FF_uses_dipoles) then
# Line 364 | Line 362 | contains
362         endif
363         haveNeighborList = .true.
364      endif
365 +
366      
367 +    
368    end subroutine init_FF
369    
370  
371    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
372    !------------------------------------------------------------->
373 <  subroutine do_force_loop(q, qcom, A, u_l, f, t, tau, pot, &
373 >  subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
374         do_pot_c, do_stress_c, error)
375      !! Position array provided by C, dimensioned by getNlocal
376 <    real ( kind = dp ), dimension(3,nLocal) :: q
376 >    real ( kind = dp ), dimension(3, nLocal) :: q
377      !! molecular center-of-mass position array
378 <    real ( kind = dp ), dimension(3,nLocal) :: qcom
378 >    real ( kind = dp ), dimension(3, nGroups) :: q_group
379      !! Rotation Matrix for each long range particle in simulation.
380 <    real( kind = dp), dimension(9,nLocal) :: A    
380 >    real( kind = dp), dimension(9, nLocal) :: A    
381      !! Unit vectors for dipoles (lab frame)
382      real( kind = dp ), dimension(3,nLocal) :: u_l
383      !! Force array provided by C, dimensioned by getNlocal
# Line 391 | Line 391 | contains
391      logical ( kind = 2) :: do_pot_c, do_stress_c
392      logical :: do_pot
393      logical :: do_stress
394 +    logical :: in_switching_region
395   #ifdef IS_MPI
396      real( kind = DP ) :: pot_local
397 <    integer :: nrow
398 <    integer :: ncol
397 >    integer :: nAtomsInRow
398 >    integer :: nAtomsInCol
399      integer :: nprocs
400 +    integer :: nGroupsInRow
401 +    integer :: nGroupsInCol
402   #endif
403      integer :: natoms    
404      logical :: update_nlist  
405 <    integer :: i, j, jbeg, jend, jnab
405 >    integer :: i, j, jstart, jend, jnab
406 >    integer :: istart, iend
407 >    integer :: ia, jb, atom1, atom2
408      integer :: nlist
409 <    real( kind = DP ) ::  rijsq, rcijsq
410 <    real(kind=dp),dimension(3) :: d, dc
409 >    real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
410 >    real( kind = DP ) :: sw, dswdr, swderiv, mf
411 >    real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
412      real(kind=dp) :: rfpot, mu_i, virial
413 <    integer :: me_i, me_j
413 >    integer :: me_i, me_j, n_in_i, n_in_j
414      logical :: is_dp_i
415      integer :: neighborListSize
416      integer :: listerror, error
417      integer :: localError
418      integer :: propPack_i, propPack_j
419 +    integer :: loopStart, loopEnd, loop
420  
421      real(kind=dp) :: listSkin = 1.0  
422      
# Line 417 | Line 424 | contains
424      
425   #ifdef IS_MPI
426      pot_local = 0.0_dp
427 <    nrow   = getNrow(plan_row)
428 <    ncol   = getNcol(plan_col)
427 >    nAtomsInRow   = getNatomsInRow(plan_atom_row)
428 >    nAtomsInCol   = getNatomsInCol(plan_atom_col)
429 >    nGroupsInRow  = getNgroupsInRow(plan_group_row)
430 >    nGroupsInCol  = getNgroupsInCol(plan_group_col)
431 >    write(*,*) nAtomsInRow, nAtomsInCol, nGroupsInRow, nGroupsInCol
432 >    write(*,*) pot_local
433   #else
434      natoms = nlocal
435   #endif
# Line 438 | Line 449 | contains
449      
450   #ifdef IS_MPI    
451      
452 <    call gather(q,q_Row,plan_row3d)
453 <    call gather(q,q_Col,plan_col3d)
454 <    
455 <    if (SIM_uses_molecular_cutoffs) then
456 <       call gather(qcom,qcom_Row,plan_row3d)
457 <       call gather(qcom,qcom_Col,plan_col3d)
447 <    endif
448 <    
452 >    call gather(q, q_Row, plan_atom_row_3d)
453 >    call gather(q, q_Col, plan_atom_col_3d)
454 >
455 >    call gather(q_group, q_group_Row, plan_group_row_3d)
456 >    call gather(q_group, q_group_Col, plan_group_col_3d)
457 >        
458      if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
459 <       call gather(u_l,u_l_Row,plan_row3d)
460 <       call gather(u_l,u_l_Col,plan_col3d)
459 >       call gather(u_l, u_l_Row, plan_atom_row_3d)
460 >       call gather(u_l, u_l_Col, plan_atom_col_3d)
461        
462 <       call gather(A,A_Row,plan_row_rotation)
463 <       call gather(A,A_Col,plan_col_rotation)
462 >       call gather(A, A_Row, plan_atom_row_rotation)
463 >       call gather(A, A_Col, plan_atom_col_rotation)
464      endif
465      
466   #endif
# Line 462 | Line 471 | contains
471      nloops = nloops + 1
472   #endif
473      
474 +    loopEnd = PAIR_LOOP
475      if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
476 <       !! See if we need to update neighbor lists
477 <       if (SIM_uses_molecular_cutoffs) then
478 <          call checkNeighborList(nlocal, qcom, listSkin, update_nlist)
479 <       else
480 <          call checkNeighborList(nlocal, q, listSkin, update_nlist)  
481 <       endif
482 <       !! if_mpi_gather_stuff_for_prepair
483 <       !! do_prepair_loop_if_needed
484 <       !! if_mpi_scatter_stuff_from_prepair
485 <       !! if_mpi_gather_stuff_from_prepair_to_main_loop
476 <      
477 <       !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
476 >       loopStart = PREPAIR_LOOP
477 >    else
478 >       loopStart = PAIR_LOOP
479 >    endif
480 >
481 >    do loop = loopStart, loopEnd
482 >
483 >       ! See if we need to update neighbor lists
484 >       ! (but only on the first time through):
485 >       if (loop .eq. loopStart) then
486   #ifdef IS_MPI
487 <      
488 <       if (update_nlist) then
489 <          
490 <          !! save current configuration, construct neighbor list,
491 <          !! and calculate forces
492 <          if (SIM_uses_molecular_cutoffs) then
485 <             call saveNeighborList(nlocal, qcom)
486 <          else
487 <             call saveNeighborList(nlocal, q)
488 <          endif
489 <          
490 <          neighborListSize = size(list)
491 <          nlist = 0      
492 <          
493 <          do i = 1, nrow
494 <             point(i) = nlist + 1
495 <            
496 <             prepair_inner: do j = 1, ncol
497 <                
498 <                if (skipThisPair(i,j)) cycle prepair_inner
499 <                
500 <                if (SIM_uses_molecular_cutoffs) then
501 <                   call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
502 <                        dc, rcijsq)
503 <                else
504 <                   call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
505 <                        dc, rcijsq)
506 <                endif
507 <                
508 <                if (rcijsq < rlistsq) then            
509 <                  
510 <                   nlist = nlist + 1
511 <                  
512 <                   if (nlist > neighborListSize) then
513 <                      call expandNeighborList(nlocal, listerror)
514 <                      if (listerror /= 0) then
515 <                         error = -1
516 <                         write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
517 <                         return
518 <                      end if
519 <                      neighborListSize = size(list)
520 <                   endif
521 <                  
522 <                   list(nlist) = j
523 <                  
524 <                   if (SIM_uses_molecular_cutoffs) then
525 <                      ! since the simulation distances were in molecular COMs:
526 <                      call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
527 <                           d, rijsq)
528 <                   else
529 <                      d(1:3) = dc(1:3)
530 <                      rijsq = rcijsq
531 <                   endif
532 <                  
533 <                   call do_prepair(i, j, rijsq, d, rcijsq, dc, &
534 <                        do_pot, do_stress, u_l, A, f, t, pot_local)
535 <                endif
536 <             enddo prepair_inner
537 <          enddo
538 <          
539 <          point(nrow + 1) = nlist + 1
540 <          
541 <       else  !! (of update_check)
542 <          
543 <          ! use the list to find the neighbors
544 <          do i = 1, nrow
545 <             JBEG = POINT(i)
546 <             JEND = POINT(i+1) - 1
547 <             ! check thiat molecule i has neighbors
548 <             if (jbeg .le. jend) then
549 <                
550 <                do jnab = jbeg, jend
551 <                   j = list(jnab)
552 <                                      
553 <                   call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
554 <                        d, rijsq)
555 <                   if (SIM_uses_molecular_cutoffs) then
556 <                      call get_interatomic_vector(qcom_Row(:,i),qcom_Col(:,j),&
557 <                           dc, rcijsq)
558 <                   else
559 <                      dc(1:3) = d(1:3)
560 <                      rcijsq = rijsq
561 <                   endif
562 <                  
563 <                   call do_prepair(i, j, rijsq, d, rcijsq, dc, &
564 <                        do_pot, do_stress, u_l, A, f, t, pot_local)
565 <                  
566 <                enddo
567 <             endif
568 <          enddo
487 >          call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
488 >             update_nlist)
489 > #else
490 >          call checkNeighborList(nGroups, q_group, listSkin, &
491 >             update_nlist)
492 > #endif
493         endif
494        
571 #else
572      
495         if (update_nlist) then
496 <          
497 <          ! save current configuration, contruct neighbor list,
498 <          ! and calculate forces
499 <          call saveNeighborList(natoms, q)
500 <          
496 >          !! save current configuration and construct neighbor list
497 > #ifdef IS_MPI
498 >          call saveNeighborList(nGroupsInRow, q_group_row)
499 > #else
500 >          call saveNeighborList(nGroups, q_group)
501 > #endif        
502            neighborListSize = size(list)
580          
503            nlist = 0
504 +       endif
505 +      
506 +       istart = 1
507 + #ifdef IS_MPI
508 +       iend = nGroupsInRow
509 + #else
510 +       iend = nGroups - 1
511 + #endif
512 +       outer: do i = istart, iend
513 +
514 +          if (update_nlist) point(i) = nlist + 1
515            
516 <          do i = 1, natoms-1
517 <             point(i) = nlist + 1
518 <            
519 <             prepair_inner: do j = i+1, natoms
520 <                
521 <                if (skipThisPair(i,j))  cycle prepair_inner
522 <                
523 <                if (SIM_uses_molecular_cutoffs) then
524 <                   call get_interatomic_vector(qcom(:,i), qcom(:,j), &
525 <                        dc, rcijsq)
526 <                else
527 <                   call get_interatomic_vector(q(:,i), q(:,j), dc, rcijsq)
528 <                endif
529 <                
530 <                if (rcijsq < rlistsq) then
531 <                  
516 >          n_in_i = groupStartRow(i+1) - groupStartRow(i)
517 >          
518 >          if (update_nlist) then
519 > #ifdef IS_MPI
520 >             jstart = 1
521 >             jend = nGroupsInCol
522 > #else
523 >             jstart = i+1
524 >             jend = nGroups
525 > #endif
526 >          else            
527 >             jstart = point(i)
528 >             jend = point(i+1) - 1
529 >             ! make sure group i has neighbors
530 >             if (jstart .gt. jend) cycle outer
531 >          endif
532 >          
533 >          do jnab = jstart, jend
534 >             if (update_nlist) then
535 >                j = jnab
536 >             else
537 >                j = list(jnab)
538 >             endif
539 >
540 > #ifdef IS_MPI
541 >             call get_interatomic_vector(q_group_Row(:,i), &
542 >                  q_group_Col(:,j), d_grp, rgrpsq)
543 > #else
544 >             call get_interatomic_vector(q_group(:,i), &
545 >                  q_group(:,j), d_grp, rgrpsq)
546 > #endif
547 >
548 >             if (rgrpsq < rlistsq) then
549 >                if (update_nlist) then
550                     nlist = nlist + 1
551                    
552                     if (nlist > neighborListSize) then
553 <                      call expandNeighborList(natoms, listerror)
553 > #ifdef IS_MPI                
554 >                      call expandNeighborList(nGroupsInRow, listerror)
555 > #else
556 >                      call expandNeighborList(nGroups, listerror)
557 > #endif
558                        if (listerror /= 0) then
559                           error = -1
560                           write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
# Line 609 | Line 564 | contains
564                     endif
565                    
566                     list(nlist) = j
612                  
613                  
614                   if (SIM_uses_molecular_cutoffs) then
615                      ! since the simulation distances were in molecular COMs:
616                      call get_interatomic_vector(q(:,i), q(:,j), &
617                           d, rijsq)
618                   else
619                      dc(1:3) = d(1:3)
620                      rcijsq = rijsq
621                   endif
622                  
623                   call do_prepair(i, j, rijsq, d, rcijsq, dc, &
624                        do_pot, do_stress, u_l, A, f, t, pot)
625                  
567                  endif
627             enddo prepair_inner
628          enddo
629          
630          point(natoms) = nlist + 1
631          
632       else !! (update)
633          
634          ! use the list to find the neighbors
635          do i = 1, natoms-1
636             JBEG = POINT(i)
637             JEND = POINT(i+1) - 1
638             ! check thiat molecule i has neighbors
639             if (jbeg .le. jend) then
568                  
569 <                do jnab = jbeg, jend
570 <                   j = list(jnab)
569 >                if (loop .eq. PAIR_LOOP) then
570 >                   vij = 0.0d0
571 >                   fij(1:3) = 0.0d0
572 >                endif
573 >                
574 >                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
575 >                     in_switching_region)
576 >                
577 >                n_in_j = groupStartCol(j+1) - groupStartCol(j)
578 >                
579 >                do ia = groupStartRow(i), groupStartRow(i+1)-1
580                    
581 <                   call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
582 <                   if (SIM_uses_molecular_cutoffs) then
583 <                      call get_interatomic_vector(qcom(:,i), qcom(:,j), &
584 <                           dc, rcijsq)
585 <                   else
586 <                      dc(1:3) = d(1:3)
587 <                      rcijsq = rijsq
581 >                   atom1 = groupListRow(ia)
582 >                  
583 >                   inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
584 >                      
585 >                      atom2 = groupListCol(jb)
586 >                      
587 >                      if (skipThisPair(atom1, atom2)) cycle inner
588 >
589 >                      if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
590 >                         d_atm(1:3) = d_grp(1:3)
591 >                         ratmsq = rgrpsq
592 >                      else
593 > #ifdef IS_MPI
594 >                         call get_interatomic_vector(q_Row(:,atom1), &
595 >                              q_Col(:,atom2), d_atm, ratmsq)
596 > #else
597 >                         call get_interatomic_vector(q(:,atom1), &
598 >                              q(:,atom2), d_atm, ratmsq)
599 > #endif
600 >                      endif
601 > #ifdef IS_MPI
602 >                      write(*,'(a20,2i8,es12.3,2i8)') 'atom1, atom2, pot = ', atom1, atom2, ratmsq, AtomRowToGlobal(atom1), AtomColToGlobal(atom2)
603 > #endif
604 >
605 >                      if (loop .eq. PREPAIR_LOOP) then
606 > #ifdef IS_MPI                      
607 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
608 >                              rgrpsq, d_grp, do_pot, do_stress, &
609 >                              u_l, A, f, t, pot_local)
610 > #else
611 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
612 >                              rgrpsq, d_grp, do_pot, do_stress, &
613 >                              u_l, A, f, t, pot)
614 > #endif                                              
615 >                      else
616 > #ifdef IS_MPI                      
617 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
618 >                              do_pot, &
619 >                              u_l, A, f, t, pot_local, vpair, fpair)
620 >                         write(*,'(a20,2i11,2es12.3)') 'atom1, atom2, pot = ', atom1, atom2, pot_local, vpair
621 > #else
622 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
623 >                              do_pot,  &
624 >                              u_l, A, f, t, pot, vpair, fpair)
625 > #endif
626 >
627 >                         vij = vij + vpair
628 >                         fij(1:3) = fij(1:3) + fpair(1:3)
629 >                      endif
630 >                   enddo inner
631 >                enddo
632 >                
633 >                if (loop .eq. PAIR_LOOP) then
634 >                   if (in_switching_region) then
635 >                      swderiv = vij*dswdr/rgrp
636 >                      fij(1) = fij(1) + swderiv*d_grp(1)
637 >                      fij(2) = fij(2) + swderiv*d_grp(2)
638 >                      fij(3) = fij(3) + swderiv*d_grp(3)
639 >                      
640 >                      do ia=groupStartRow(i), groupStartRow(i+1)-1
641 >                         atom1=groupListRow(ia)
642 >                         mf = mfactRow(atom1)
643 > #ifdef IS_MPI
644 >                         f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
645 >                         f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
646 >                         f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
647 > #else
648 >                         f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
649 >                         f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
650 >                         f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
651 > #endif
652 >                      enddo
653 >                      
654 >                      do jb=groupStartCol(j), groupStartCol(j+1)-1
655 >                         atom2=groupListCol(jb)
656 >                         mf = mfactCol(atom2)
657 > #ifdef IS_MPI
658 >                         f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
659 >                         f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
660 >                         f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
661 > #else
662 >                         f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
663 >                         f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
664 >                         f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
665 > #endif
666 >                      enddo
667                     endif
668                    
669 <                   call do_prepair(i, j, rijsq, d, rcijsq, dc, &
670 <                        do_pot, do_stress, u_l, A, f, t, pot)
671 <                  
656 <                enddo
657 <             endif
669 >                   if (do_stress) call add_stress_tensor(d_grp, fij)
670 >                endif
671 >             end if
672            enddo
673 <       endif
660 < #endif
661 <       !! Do rest of preforce calculations
662 <       !! do necessary preforce calculations  
663 <       call do_preforce(nlocal,pot)
664 <       ! we have already updated the neighbor list set it to false...
665 <       update_nlist = .false.
666 <    else
667 <       !! See if we need to update neighbor lists for non pre-pair
668 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
669 <    endif
670 <    
671 <    !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>
672 <    
673 < #ifdef IS_MPI
674 <    
675 <    if (update_nlist) then
676 <       !! save current configuration, construct neighbor list,
677 <       !! and calculate forces
678 <       call saveNeighborList(nlocal, q)
673 >       enddo outer
674        
675 <       neighborListSize = size(list)
676 <       nlist = 0      
677 <      
678 <       do i = 1, nrow
679 <          
680 <          point(i) = nlist + 1
681 <          
682 <          inner: do j = 1, ncol
683 <            
684 <             if (skipThisPair(i,j)) cycle inner
685 <            
691 <             if (SIM_uses_molecular_cutoffs) then
692 <                call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
693 <                     dc, rcijsq)
694 <             else
695 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
696 <                     dc, rcijsq)
697 <             endif
698 <            
699 <             if (rcijsq < rlistsq) then            
700 <                
701 <                nlist = nlist + 1
702 <                
703 <                if (nlist > neighborListSize) then
704 <                   call expandNeighborList(nlocal, listerror)
705 <                   if (listerror /= 0) then
706 <                      error = -1
707 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
708 <                      return
709 <                   end if
710 <                   neighborListSize = size(list)
711 <                endif
712 <                
713 <                list(nlist) = j
714 <                
715 <                if (SIM_uses_molecular_cutoffs) then
716 <                   call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
717 <                        d, rijsq)
718 <                else
719 <                   d(1:3) = dc(1:3)
720 <                   rijsq = rcijsq
721 <                endif
722 <                
723 <                call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
724 <                     do_pot, do_stress, u_l, A, f, t, pot_local)
725 <                
726 <             endif
727 <          enddo inner
728 <       enddo
729 <      
730 <       point(nrow + 1) = nlist + 1
731 <      
732 <    else  !! (of update_check)
733 <      
734 <       ! use the list to find the neighbors
735 <       do i = 1, nrow
736 <          JBEG = POINT(i)
737 <          JEND = POINT(i+1) - 1
738 <          ! check thiat molecule i has neighbors
739 <          if (jbeg .le. jend) then
740 <            
741 <             do jnab = jbeg, jend
742 <                j = list(jnab)
743 <                
744 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
745 <                if (SIM_uses_molecular_cutoffs) then
746 <                   call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
747 <                        dc, rcijsq)
748 <                else
749 <                   dc(1:3) = d(1:3)
750 <                   rcijsq = rijsq
751 <                endif
752 <                
753 <                call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
754 <                     do_pot, do_stress, u_l, A, f, t, pot_local)
755 <                
756 <             enddo
675 >       if (update_nlist) then
676 > #ifdef IS_MPI
677 >          point(nGroupsInRow + 1) = nlist + 1
678 > #else
679 >          point(nGroups) = nlist + 1
680 > #endif
681 >          if (loop .eq. PREPAIR_LOOP) then
682 >             ! we just did the neighbor list update on the first
683 >             ! pass, so we don't need to do it
684 >             ! again on the second pass
685 >             update_nlist = .false.                              
686            endif
687 <       enddo
759 <    endif
760 <    
761 < #else
762 <    
763 <    if (update_nlist) then
764 <      
765 <       ! save current configuration, contruct neighbor list,
766 <       ! and calculate forces
767 <       call saveNeighborList(natoms, q)
768 <      
769 <       neighborListSize = size(list)
770 <      
771 <       nlist = 0
772 <      
773 <       do i = 1, natoms-1
774 <          point(i) = nlist + 1
775 <          
776 <          inner: do j = i+1, natoms
687 >       endif
688              
689 <             if (skipThisPair(i,j))  cycle inner
690 <            
691 <             if (SIM_uses_molecular_cutoffs) then
781 <                call get_interatomic_vector(qcom(:,i), qcom(:,j), &
782 <                     dc, rcijsq)
783 <             else
784 <                call get_interatomic_vector(q(:,i), q(:,j), &
785 <                     dc, rcijsq)
786 <             endif
787 <            
788 <             if (rcijsq < rlistsq) then
789 <                
790 <                nlist = nlist + 1
791 <                
792 <                if (nlist > neighborListSize) then
793 <                   call expandNeighborList(natoms, listerror)
794 <                   if (listerror /= 0) then
795 <                      error = -1
796 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
797 <                      return
798 <                   end if
799 <                   neighborListSize = size(list)
800 <                endif
801 <                
802 <                list(nlist) = j
803 <                
804 <                if (SIM_uses_molecular_cutoffs) then
805 <                   call get_interatomic_vector(q(:,i), q(:,j), &
806 <                        d, rijsq)
807 <                else
808 <                   d(1:3) = dc(1:3)
809 <                   rijsq = rcijsq
810 <                endif
811 <                
812 <                call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
813 <                     do_pot, do_stress, u_l, A, f, t, pot)
814 <                
815 <             endif
816 <          enddo inner
817 <       enddo
689 >       if (loop .eq. PREPAIR_LOOP) then
690 >          call do_preforce(nlocal, pot)
691 >       endif
692        
693 <       point(natoms) = nlist + 1
820 <      
821 <    else !! (update)
822 <      
823 <       ! use the list to find the neighbors
824 <       do i = 1, natoms-1
825 <          JBEG = POINT(i)
826 <          JEND = POINT(i+1) - 1
827 <          ! check thiat molecule i has neighbors
828 <          if (jbeg .le. jend) then
829 <            
830 <             do jnab = jbeg, jend
831 <                j = list(jnab)
832 <
833 <
834 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
835 <                if (SIM_uses_molecular_cutoffs) then
836 <                   call get_interatomic_vector(qcom(:,i), qcom(:,j), &
837 <                        dc, rcijsq)
838 <                else
839 <                   dc(1:3) = d(1:3)
840 <                   rcijsq = rijsq
841 <                endif
842 <                
843 <                call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
844 <                     do_pot, do_stress, u_l, A, f, t, pot)
845 <                
846 <             enddo
847 <          endif
848 <       enddo
849 <    endif
693 >    enddo
694      
851 #endif
852    
853    ! phew, done with main loop.
854    
695      !! Do timing
696   #ifdef PROFILE
697      call cpu_time(forceTimeFinal)
698      forceTime = forceTime + forceTimeFinal - forceTimeInitial
699 < #endif
699 > #endif    
700      
861    
701   #ifdef IS_MPI
702      !!distribute forces
703      
704      f_temp = 0.0_dp
705 <    call scatter(f_Row,f_temp,plan_row3d)
705 >    call scatter(f_Row,f_temp,plan_atom_row_3d)
706      do i = 1,nlocal
707         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
708      end do
709      
710      f_temp = 0.0_dp
711 <    call scatter(f_Col,f_temp,plan_col3d)
711 >    call scatter(f_Col,f_temp,plan_atom_col_3d)
712      do i = 1,nlocal
713         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
714      end do
715      
716      if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
717         t_temp = 0.0_dp
718 <       call scatter(t_Row,t_temp,plan_row3d)
718 >       call scatter(t_Row,t_temp,plan_atom_row_3d)
719         do i = 1,nlocal
720            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
721         end do
722         t_temp = 0.0_dp
723 <       call scatter(t_Col,t_temp,plan_col3d)
723 >       call scatter(t_Col,t_temp,plan_atom_col_3d)
724        
725         do i = 1,nlocal
726            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
# Line 890 | Line 729 | contains
729      
730      if (do_pot) then
731         ! scatter/gather pot_row into the members of my column
732 <       call scatter(pot_Row, pot_Temp, plan_row)
732 >       call scatter(pot_Row, pot_Temp, plan_atom_row)
733        
734         ! scatter/gather pot_local into all other procs
735         ! add resultant to get total pot
# Line 900 | Line 739 | contains
739        
740         pot_Temp = 0.0_DP
741        
742 <       call scatter(pot_Col, pot_Temp, plan_col)
742 >       call scatter(pot_Col, pot_Temp, plan_atom_col)
743         do i = 1, nlocal
744            pot_local = pot_local + pot_Temp(i)
745         enddo
746 <
746 >      
747      endif
748   #endif
749      
# Line 913 | Line 752 | contains
752         if (FF_uses_RF .and. SIM_uses_RF) then
753            
754   #ifdef IS_MPI
755 <          call scatter(rf_Row,rf,plan_row3d)
756 <          call scatter(rf_Col,rf_Temp,plan_col3d)
755 >          call scatter(rf_Row,rf,plan_atom_row_3d)
756 >          call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
757            do i = 1,nlocal
758               rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
759            end do
# Line 974 | Line 813 | contains
813      endif
814      
815   #endif
816 <    
978 <    
816 >      
817    end subroutine do_force_loop
818    
819 <  subroutine do_pair(i, j, rijsq, d, rcijsq, dc, mfact, do_pot, do_stress, &
820 <       u_l, A, f, t, pot)
819 >  subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
820 >       u_l, A, f, t, pot, vpair, fpair)
821  
822 <    real( kind = dp ) :: pot
822 >    real( kind = dp ) :: pot, vpair, sw
823 >    real( kind = dp ), dimension(3) :: fpair
824      real( kind = dp ), dimension(nLocal)   :: mfact
825      real( kind = dp ), dimension(3,nLocal) :: u_l
826      real( kind = dp ), dimension(9,nLocal) :: A
827      real( kind = dp ), dimension(3,nLocal) :: f
828      real( kind = dp ), dimension(3,nLocal) :: t
829  
830 <    logical, intent(inout) :: do_pot, do_stress
830 >    logical, intent(inout) :: do_pot
831      integer, intent(in) :: i, j
832 <    real ( kind = dp ), intent(inout) :: rijsq, rcijsq
833 <    real ( kind = dp )                :: r, rc
834 <    real ( kind = dp ), intent(inout) :: d(3), dc(3)
832 >    real ( kind = dp ), intent(inout) :: rijsq
833 >    real ( kind = dp )                :: r
834 >    real ( kind = dp ), intent(inout) :: d(3)
835      integer :: me_i, me_j
836  
837      r = sqrt(rijsq)
838 <    if (SIM_uses_molecular_cutoffs) then
839 <       rc = sqrt(rcijsq)
1001 <    else
1002 <       rc = r
1003 <    endif
838 >    vpair = 0.0d0
839 >    fpair(1:3) = 0.0d0
840  
1005
841   #ifdef IS_MPI
842 <    if (tagRow(i) .eq. tagColumn(j)) then
843 <       write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
842 >    if (AtomRowToGlobal(i) .eq. AtomColToGlobal(j)) then
843 >       write(0,*) 'do_pair is doing', i , j, AtomRowToGlobal(i), AtomColToGlobal(j)
844      endif
845      me_i = atid_row(i)
846      me_j = atid_col(j)
# Line 1017 | Line 852 | contains
852      if (FF_uses_LJ .and. SIM_uses_LJ) then
853        
854         if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
855 <          call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
855 >          !write(*,*) 'calling lj with'
856 >          !write(*,*) i, j, r, rijsq
857 >          !write(*,'(3es12.3)') d(1), d(2), d(3)
858 >          !write(*,'(3es12.3)') sw, vpair, pot
859 >          !write(*,*)
860 >
861 >          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
862         endif
863        
864      endif
# Line 1025 | Line 866 | contains
866      if (FF_uses_charges .and. SIM_uses_charges) then
867        
868         if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
869 <          call do_charge_pair(i, j, d, r, rijsq, dc, rc, rcijsq, mfact, &
1029 <               pot, f, do_pot, do_stress, SIM_uses_molecular_cutoffs)
869 >          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
870         endif
871        
872      endif
# Line 1034 | Line 874 | contains
874      if (FF_uses_dipoles .and. SIM_uses_dipoles) then
875        
876         if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
877 <          call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
878 <               do_pot, do_stress)
877 >          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
878 >               do_pot)
879            if (FF_uses_RF .and. SIM_uses_RF) then
880 <             call accumulate_rf(i, j, r, u_l)
881 <             call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
880 >             call accumulate_rf(i, j, r, u_l, sw)
881 >             call rf_correct_forces(i, j, d, r, u_l, sw, f, fpair)
882            endif          
883         endif
884  
# Line 1047 | Line 887 | contains
887      if (FF_uses_Sticky .and. SIM_uses_sticky) then
888  
889         if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
890 <          call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
891 <               do_pot, do_stress)
890 >          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, A, f, t, &
891 >               do_pot)
892         endif
893  
894      endif
# Line 1057 | Line 897 | contains
897      if (FF_uses_GB .and. SIM_uses_GB) then
898        
899         if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
900 <          call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
901 <               do_pot, do_stress)          
900 >          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
901 >               do_pot)
902         endif
903  
904      endif
# Line 1066 | Line 906 | contains
906      if (FF_uses_EAM .and. SIM_uses_EAM) then
907        
908         if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
909 <          call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
909 >          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
910 >               do_pot)
911         endif
912        
913      endif
914 <
914 >    
915    end subroutine do_pair
916  
917 <
1077 <
1078 <  subroutine do_prepair(i, j, rijsq, d, rcijsq, dc, &
917 >  subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
918         do_pot, do_stress, u_l, A, f, t, pot)
919 <   real( kind = dp ) :: pot
919 >
920 >   real( kind = dp ) :: pot, sw
921     real( kind = dp ), dimension(3,nLocal) :: u_l
922     real (kind=dp), dimension(9,nLocal) :: A
923     real (kind=dp), dimension(3,nLocal) :: f
# Line 1103 | Line 943 | contains
943    
944  
945   #ifdef IS_MPI
946 <   if (tagRow(i) .eq. tagColumn(j)) then
947 <      write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
946 >   if (AtomRowToGlobal(i) .eq. AtomColToGlobal(j)) then
947 >      write(0,*) 'do_prepair is doing', i , j, AtomRowToGlobal(i), AtomColToGlobal(j)
948     endif
949    
950     me_i = atid_row(i)
# Line 1116 | Line 956 | contains
956     me_j = atid(j)
957    
958   #endif
959 <    
959 >  
960     if (FF_uses_EAM .and. SIM_uses_EAM) then
961 <
961 >      
962        if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
963             call calc_EAM_prepair_rho(i, j, d, r, rijsq )
964 <
964 >      
965     endif
966    
967   end subroutine do_prepair
968 <
969 <
1130 <
1131 <
968 >
969 >
970   subroutine do_preforce(nlocal,pot)
971     integer :: nlocal
972     real( kind = dp ) :: pot
# Line 1199 | Line 1037 | contains
1037     q_Row = 0.0_dp
1038     q_Col = 0.0_dp
1039  
1040 <   qcom_Row = 0.0_dp
1041 <   qcom_Col = 0.0_dp  
1040 >   q_group_Row = 0.0_dp
1041 >   q_group_Col = 0.0_dp  
1042    
1043     u_l_Row = 0.0_dp
1044     u_l_Col = 0.0_dp
# Line 1253 | Line 1091 | contains
1091    
1092   #ifdef IS_MPI
1093     !! in MPI, we have to look up the unique IDs for each atom
1094 <   unique_id_1 = tagRow(atom1)
1094 >   unique_id_1 = AtomRowToGlobal(atom1)
1095   #else
1096     !! in the normal loop, the atom numbers are unique
1097     unique_id_1 = atom1
# Line 1272 | Line 1110 | contains
1110     end if
1111    
1112   #ifdef IS_MPI
1113 <   unique_id_2 = tagColumn(atom2)
1113 >   unique_id_2 = AtomColToGlobal(atom2)
1114   #else
1115     unique_id_2 = atom2
1116   #endif
# Line 1307 | Line 1145 | contains
1145        endif
1146     enddo
1147    
1148 <   do i = 1, nExcludes_local
1149 <      if (excludesLocal(1,i) == unique_id_1) then
1150 <         if (excludesLocal(2,i) == unique_id_2) then
1151 <            skip_it = .true.
1314 <            return
1315 <         endif
1316 <      else
1317 <         if (excludesLocal(1,i) == unique_id_2) then
1318 <            if (excludesLocal(2,i) == unique_id_1) then
1319 <               skip_it = .true.
1320 <               return
1321 <            endif
1322 <         endif
1148 >   do i = 1, nSkipsForAtom(atom1)
1149 >      if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1150 >         skip_it = .true.
1151 >         return
1152        endif
1153     end do
1154    
# Line 1350 | Line 1179 | contains
1179   #endif
1180  
1181   !! This cleans componets of force arrays belonging only to fortran
1182 +
1183 + subroutine add_stress_tensor(dpair, fpair)
1184 +  
1185 +   real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1186 +  
1187 +   ! because the d vector is the rj - ri vector, and
1188 +   ! because fx, fy, fz are the force on atom i, we need a
1189 +   ! negative sign here:  
1190 +  
1191 +   tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1192 +   tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1193 +   tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1194 +   tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1195 +   tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1196 +   tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1197 +   tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1198 +   tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1199 +   tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1200 +  
1201 +   !write(*,'(6es12.3)')  fpair(1:3), tau_Temp(1), tau_Temp(5), tau_temp(9)
1202 +   virial_Temp = virial_Temp + &
1203 +        (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1204 +  
1205 + end subroutine add_stress_tensor
1206  
1207   end module do_Forces
1208 +

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines