ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90 (file contents):
Revision 1930 by gezelter, Wed Jan 12 22:41:40 2005 UTC vs.
Revision 2220 by chrisfen, Thu May 5 14:47:35 2005 UTC

# Line 48 | Line 48
48   !! Corresponds to the force field defined in ssd_FF.cpp
49   !! @author Charles F. Vardeman II
50   !! @author Matthew Meineke
51 < !! @author Christopher Fennel
51 > !! @author Christopher Fennell
52   !! @author J. Daniel Gezelter
53 < !! @version $Id: sticky.F90,v 1.3 2005-01-12 22:40:45 gezelter Exp $, $Date: 2005-01-12 22:40:45 $, $Name: not supported by cvs2svn $, $Revision: 1.3 $
53 > !! @version $Id: sticky.F90,v 1.8 2005-05-05 14:47:35 chrisfen Exp $, $Date: 2005-05-05 14:47:35 $, $Name: not supported by cvs2svn $, $Revision: 1.8 $
54  
55   module sticky
56  
# Line 69 | Line 69 | module sticky
69  
70    public :: newStickyType
71    public :: do_sticky_pair
72 +  public :: destroyStickyTypes
73 +  public :: do_sticky_power_pair
74  
75  
76    type :: StickyList
# Line 82 | Line 84 | module sticky
84       real( kind = dp ) :: rup = 0.0_dp
85       real( kind = dp ) :: rbig = 0.0_dp
86    end type StickyList
87 <  
87 >
88    type(StickyList), dimension(:),allocatable :: StickyMap
89  
90   contains
# Line 96 | Line 98 | contains
98      real( kind = dp ), intent(in) :: rlp, rup
99      integer :: nATypes, myATID
100  
101 <    
101 >
102      isError = 0
103      myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
104 <    
104 >
105      !! Be simple-minded and assume that we need a StickyMap that
106      !! is the same size as the total number of atom types
107  
# Line 128 | Line 130 | contains
130      StickyMap(myATID)%c_ident = c_ident
131  
132      ! we could pass all 5 parameters if we felt like it...
133 <    
133 >
134      StickyMap(myATID)%w0 = w0
135      StickyMap(myATID)%v0 = v0
136      StickyMap(myATID)%v0p = v0p
# Line 142 | Line 144 | contains
144      else
145         StickyMap(myATID)%rbig = StickyMap(myATID)%rup
146      endif
147 <  
147 >
148      return
149    end subroutine newStickyType
150  
151    subroutine do_sticky_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
152         pot, A, f, t, do_pot)
153 <    
153 >
154      !! This routine does only the sticky portion of the SSD potential
155      !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
156      !! The Lennard-Jones and dipolar interaction must be handled separately.
157 <    
157 >
158      !! We assume that the rotation matrices have already been calculated
159      !! and placed in the A array.
160  
# Line 186 | Line 188 | contains
188      real (kind=dp) :: radcomxj, radcomyj, radcomzj
189      integer :: id1, id2
190      integer :: me1, me2
191 <   real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
191 >    real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
192  
193 < if (.not.allocated(StickyMap)) then
193 >    if (.not.allocated(StickyMap)) then
194         call handleError("sticky", "no StickyMap was present before first call of do_sticky_pair!")
195         return
196      end if
197 <    
197 >
198   #ifdef IS_MPI
199      me1 = atid_Row(atom1)
200      me2 = atid_Col(atom2)
# Line 460 | Line 462 | if (.not.allocated(StickyMap)) then
462         id1 = atom1
463         id2 = atom2
464   #endif
465 <      
465 >
466         if (molMembershipList(id1) .ne. molMembershipList(id2)) then
467 <          
467 >
468            fpair(1) = fpair(1) + fxradial
469            fpair(2) = fpair(2) + fyradial
470            fpair(3) = fpair(3) + fzradial
471 <          
471 >
472         endif
473      endif
474    end subroutine do_sticky_pair
475  
476    !! calculates the switching functions and their derivatives for a given
477    subroutine calc_sw_fnc(r, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
478 <    
478 >
479      real (kind=dp), intent(in) :: r, rl, ru, rlp, rup
480      real (kind=dp), intent(inout) :: s, sp, dsdr, dspdr
481 <    
481 >
482      ! distances must be in angstroms
483 <    
483 >
484      if (r.lt.rl) then
485         s = 1.0d0
486         dsdr = 0.0d0
# Line 502 | Line 504 | if (.not.allocated(StickyMap)) then
504              ((rup - rlp)**3)
505         dspdr = 6.0d0*(r-rup)*(r-rlp)/((rup - rlp)**3)      
506      endif
507 <    
507 >
508      return
509    end subroutine calc_sw_fnc
508 end module sticky
510  
511 <  subroutine newStickyType(c_ident, w0, v0, v0p, rl, ru, rlp, rup, isError)
512 <
513 <    use definitions, ONLY : dp  
514 <    use sticky, ONLY : module_newStickyType => newStickyType
511 >  subroutine destroyStickyTypes()  
512 >    if(allocated(StickyMap)) deallocate(StickyMap)
513 >  end subroutine destroyStickyTypes
514 >  
515 >    subroutine do_sticky_power_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
516 >       pot, A, f, t, do_pot)
517 >    !! We assume that the rotation matrices have already been calculated
518 >    !! and placed in the A array.
519  
520 <    integer, intent(inout) :: c_ident, isError
521 <    real( kind = dp ), intent(inout) :: w0, v0, v0p, rl, ru, rlp, rup
522 <    
523 <    call module_newStickyType(c_ident, w0, v0, v0p, rl, ru, rlp, rup, &
524 <         isError)
525 <    
526 <  end subroutine newStickyType
520 >    !! i and j are pointers to the two SSD atoms
521 >
522 >    integer, intent(in) :: atom1, atom2
523 >    real (kind=dp), intent(inout) :: rij, r2
524 >    real (kind=dp), dimension(3), intent(in) :: d
525 >    real (kind=dp), dimension(3), intent(inout) :: fpair
526 >    real (kind=dp) :: pot, vpair, sw
527 >    real (kind=dp), dimension(9,nLocal) :: A
528 >    real (kind=dp), dimension(3,nLocal) :: f
529 >    real (kind=dp), dimension(3,nLocal) :: t
530 >    logical, intent(in) :: do_pot
531 >
532 >    real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
533 >    real (kind=dp) :: r3, r5, r6, s, sp, dsdr, dspdr
534 >    real (kind=dp) :: wi, wj, w, wip, wjp, wp, wi2, wj2
535 >    real (kind=dp) :: dwidx, dwidy, dwidz, dwjdx, dwjdy, dwjdz
536 >    real (kind=dp) :: dwipdx, dwipdy, dwipdz, dwjpdx, dwjpdy, dwjpdz
537 >    real (kind=dp) :: dwidux, dwiduy, dwiduz, dwjdux, dwjduy, dwjduz
538 >    real (kind=dp) :: dwipdux, dwipduy, dwipduz, dwjpdux, dwjpduy, dwjpduz
539 >    real (kind=dp) :: zif, zis, zjf, zjs, uglyi, uglyj
540 >    real (kind=dp) :: drdx, drdy, drdz
541 >    real (kind=dp) :: txi, tyi, tzi, txj, tyj, tzj
542 >    real (kind=dp) :: fxii, fyii, fzii, fxjj, fyjj, fzjj
543 >    real (kind=dp) :: fxij, fyij, fzij, fxji, fyji, fzji      
544 >    real (kind=dp) :: fxradial, fyradial, fzradial
545 >    real (kind=dp) :: rijtest, rjitest
546 >    real (kind=dp) :: radcomxi, radcomyi, radcomzi
547 >    real (kind=dp) :: radcomxj, radcomyj, radcomzj
548 >    integer :: id1, id2
549 >    integer :: me1, me2
550 >    real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
551 >
552 >    if (.not.allocated(StickyMap)) then
553 >       call handleError("sticky", "no StickyMap was present before first call of do_sticky_power_pair!")
554 >       return
555 >    end if
556 >
557 > #ifdef IS_MPI
558 >    me1 = atid_Row(atom1)
559 >    me2 = atid_Col(atom2)
560 > #else
561 >    me1 = atid(atom1)
562 >    me2 = atid(atom2)
563 > #endif
564 >
565 >    if (me1.eq.me2) then
566 >       w0  = StickyMap(me1)%w0
567 >       v0  = StickyMap(me1)%v0
568 >       v0p = StickyMap(me1)%v0p
569 >       rl  = StickyMap(me1)%rl
570 >       ru  = StickyMap(me1)%ru
571 >       rlp = StickyMap(me1)%rlp
572 >       rup = StickyMap(me1)%rup
573 >       rbig = StickyMap(me1)%rbig
574 >    else
575 >       ! This is silly, but if you want 2 sticky types in your
576 >       ! simulation, we'll let you do it with the Lorentz-
577 >       ! Berthelot mixing rules.
578 >       ! (Warning: you'll be SLLLLLLLLLLLLLLLOOOOOOOOOOWWWWWWWWWWW)
579 >       rl   = 0.5_dp * ( StickyMap(me1)%rl + StickyMap(me2)%rl )
580 >       ru   = 0.5_dp * ( StickyMap(me1)%ru + StickyMap(me2)%ru )
581 >       rlp  = 0.5_dp * ( StickyMap(me1)%rlp + StickyMap(me2)%rlp )
582 >       rup  = 0.5_dp * ( StickyMap(me1)%rup + StickyMap(me2)%rup )
583 >       rbig = max(ru, rup)
584 >       w0  = sqrt( StickyMap(me1)%w0   * StickyMap(me2)%w0  )
585 >       v0  = sqrt( StickyMap(me1)%v0   * StickyMap(me2)%v0  )
586 >       v0p = sqrt( StickyMap(me1)%v0p  * StickyMap(me2)%v0p )
587 >    endif
588 >
589 >    if ( rij .LE. rbig ) then
590 >
591 >       r3 = r2*rij
592 >       r5 = r3*r2
593 >
594 >       drdx = d(1) / rij
595 >       drdy = d(2) / rij
596 >       drdz = d(3) / rij
597 >
598 > #ifdef IS_MPI
599 >       ! rotate the inter-particle separation into the two different
600 >       ! body-fixed coordinate systems:
601 >
602 >       xi = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
603 >       yi = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
604 >       zi = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
605 >
606 >       ! negative sign because this is the vector from j to i:
607 >
608 >       xj = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
609 >       yj = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
610 >       zj = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
611 > #else
612 >       ! rotate the inter-particle separation into the two different
613 >       ! body-fixed coordinate systems:
614 >
615 >       xi = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
616 >       yi = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
617 >       zi = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
618 >
619 >       ! negative sign because this is the vector from j to i:
620 >
621 >       xj = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
622 >       yj = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
623 >       zj = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
624 > #endif
625 >
626 >       xi2 = xi*xi
627 >       yi2 = yi*yi
628 >       zi2 = zi*zi
629 >
630 >       xj2 = xj*xj
631 >       yj2 = yj*yj
632 >       zj2 = zj*zj
633 >
634 >       call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
635 >
636 >       wi = 2.0d0*(xi2-yi2)*zi / r3
637 >       wj = 2.0d0*(xj2-yj2)*zj / r3
638 >       !rootwi = sqrt(abs(wi))
639 >       !rootwj = sqrt(abs(wj))
640 >       wi2 = wi*wi
641 >       wj2 = wj*wj
642 >
643 >      
644 >       w = wi*wi2+wj*wj2
645 >
646 >       zif = zi/rij - 0.6d0
647 >       zis = zi/rij + 0.8d0
648 >
649 >       zjf = zj/rij - 0.6d0
650 >       zjs = zj/rij + 0.8d0
651 >
652 >       wip = zif*zif*zis*zis - w0
653 >       wjp = zjf*zjf*zjs*zjs - w0
654 >       wp = wip + wjp
655 >
656 >       vpair = vpair + 0.5d0*(v0*s*w + v0p*sp*wp)
657 >       if (do_pot) then
658 > #ifdef IS_MPI
659 >          pot_row(atom1) = pot_row(atom1) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
660 >          pot_col(atom2) = pot_col(atom2) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
661 > #else
662 >          pot = pot + 0.5d0*(v0*s*w + v0p*sp*wp)*sw
663 > #endif  
664 >       endif
665 >
666 > !       dwidx = 1.5d0*rootwi*( 4.0d0*xi*zi/r3 - 6.0d0*xi*zi*(xi2-yi2)/r5 )
667 > !       dwidy = 1.5d0*rootwi*( -4.0d0*yi*zi/r3 - 6.0d0*yi*zi*(xi2-yi2)/r5 )
668 > !       dwidz = 1.5d0*rootwi*( 2.0d0*(xi2-yi2)/r3 - 6.0d0*zi2*(xi2-yi2)/r5 )
669 >
670 > !       dwjdx = 1.5d0*rootwj*( 4.0d0*xj*zj/r3  - 6.0d0*xj*zj*(xj2-yj2)/r5 )
671 > !       dwjdy = 1.5d0*rootwj*( -4.0d0*yj*zj/r3  - 6.0d0*yj*zj*(xj2-yj2)/r5 )
672 > !       dwjdz = 1.5d0*rootwj*( 2.0d0*(xj2-yj2)/r3  - 6.0d0*zj2*(xj2-yj2)/r5 )
673 >      
674 >       dwidx = 3.0d0*wi2*( 4.0d0*xi*zi/r3 - 6.0d0*xi*zi*(xi2-yi2)/r5 )
675 >       dwidy = 3.0d0*wi2*( -4.0d0*yi*zi/r3 - 6.0d0*yi*zi*(xi2-yi2)/r5 )
676 >       dwidz = 3.0d0*wi2*( 2.0d0*(xi2-yi2)/r3 - 6.0d0*zi2*(xi2-yi2)/r5 )
677 >
678 >       dwjdx = 3.0d0*wj2*( 4.0d0*xj*zj/r3  - 6.0d0*xj*zj*(xj2-yj2)/r5 )
679 >       dwjdy = 3.0d0*wj2*( -4.0d0*yj*zj/r3  - 6.0d0*yj*zj*(xj2-yj2)/r5 )
680 >       dwjdz = 3.0d0*wj2*( 2.0d0*(xj2-yj2)/r3  - 6.0d0*zj2*(xj2-yj2)/r5 )
681 >
682 >       uglyi = zif*zif*zis + zif*zis*zis
683 >       uglyj = zjf*zjf*zjs + zjf*zjs*zjs
684 >
685 >       dwipdx = -2.0d0*xi*zi*uglyi/r3
686 >       dwipdy = -2.0d0*yi*zi*uglyi/r3
687 >       dwipdz = 2.0d0*(1.0d0/rij - zi2/r3)*uglyi
688 >
689 >       dwjpdx = -2.0d0*xj*zj*uglyj/r3
690 >       dwjpdy = -2.0d0*yj*zj*uglyj/r3
691 >       dwjpdz = 2.0d0*(1.0d0/rij - zj2/r3)*uglyj
692 >
693 > !       dwidux = 1.5d0*rootwi*( 4.0d0*(yi*zi2 + 0.5d0*yi*(xi2-yi2))/r3 )
694 > !       dwiduy = 1.5d0*rootwi*( 4.0d0*(xi*zi2 - 0.5d0*xi*(xi2-yi2))/r3 )
695 > !       dwiduz = 1.5d0*rootwi*( -8.0d0*xi*yi*zi/r3 )
696 >
697 > !       dwjdux = 1.5d0*rootwj*( 4.0d0*(yj*zj2 + 0.5d0*yj*(xj2-yj2))/r3 )
698 > !       dwjduy = 1.5d0*rootwj*( 4.0d0*(xj*zj2 - 0.5d0*xj*(xj2-yj2))/r3 )
699 > !       dwjduz = 1.5d0*rootwj*( -8.0d0*xj*yj*zj/r3 )
700 >      
701 >       dwidux = 3.0d0*wi2*( 4.0d0*(yi*zi2 + 0.5d0*yi*(xi2-yi2))/r3 )
702 >       dwiduy = 3.0d0*wi2*( 4.0d0*(xi*zi2 - 0.5d0*xi*(xi2-yi2))/r3 )
703 >       dwiduz = 3.0d0*wi2*( -8.0d0*xi*yi*zi/r3 )
704 >
705 >       dwjdux = 3.0d0*wj2*( 4.0d0*(yj*zj2 + 0.5d0*yj*(xj2-yj2))/r3 )
706 >       dwjduy = 3.0d0*wj2*( 4.0d0*(xj*zj2 - 0.5d0*xj*(xj2-yj2))/r3 )
707 >       dwjduz = 3.0d0*wj2*( -8.0d0*xj*yj*zj/r3 )
708 >
709 >       dwipdux =  2.0d0*yi*uglyi/rij
710 >       dwipduy = -2.0d0*xi*uglyi/rij
711 >       dwipduz =  0.0d0
712 >
713 >       dwjpdux =  2.0d0*yj*uglyj/rij
714 >       dwjpduy = -2.0d0*xj*uglyj/rij
715 >       dwjpduz =  0.0d0
716 >
717 >       ! do the torques first since they are easy:
718 >       ! remember that these are still in the body fixed axes
719 >
720 >       txi = 0.5d0*(v0*s*dwidux + v0p*sp*dwipdux)*sw
721 >       tyi = 0.5d0*(v0*s*dwiduy + v0p*sp*dwipduy)*sw
722 >       tzi = 0.5d0*(v0*s*dwiduz + v0p*sp*dwipduz)*sw
723 >
724 >       txj = 0.5d0*(v0*s*dwjdux + v0p*sp*dwjpdux)*sw
725 >       tyj = 0.5d0*(v0*s*dwjduy + v0p*sp*dwjpduy)*sw
726 >       tzj = 0.5d0*(v0*s*dwjduz + v0p*sp*dwjpduz)*sw
727 >
728 >       ! go back to lab frame using transpose of rotation matrix:
729 >
730 > #ifdef IS_MPI
731 >       t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*txi + &
732 >            a_Row(4,atom1)*tyi + a_Row(7,atom1)*tzi
733 >       t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*txi + &
734 >            a_Row(5,atom1)*tyi + a_Row(8,atom1)*tzi
735 >       t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*txi + &
736 >            a_Row(6,atom1)*tyi + a_Row(9,atom1)*tzi
737 >
738 >       t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*txj + &
739 >            a_Col(4,atom2)*tyj + a_Col(7,atom2)*tzj
740 >       t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*txj + &
741 >            a_Col(5,atom2)*tyj + a_Col(8,atom2)*tzj
742 >       t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*txj + &
743 >            a_Col(6,atom2)*tyj + a_Col(9,atom2)*tzj
744 > #else
745 >       t(1,atom1) = t(1,atom1) + a(1,atom1)*txi + a(4,atom1)*tyi + a(7,atom1)*tzi
746 >       t(2,atom1) = t(2,atom1) + a(2,atom1)*txi + a(5,atom1)*tyi + a(8,atom1)*tzi
747 >       t(3,atom1) = t(3,atom1) + a(3,atom1)*txi + a(6,atom1)*tyi + a(9,atom1)*tzi
748 >
749 >       t(1,atom2) = t(1,atom2) + a(1,atom2)*txj + a(4,atom2)*tyj + a(7,atom2)*tzj
750 >       t(2,atom2) = t(2,atom2) + a(2,atom2)*txj + a(5,atom2)*tyj + a(8,atom2)*tzj
751 >       t(3,atom2) = t(3,atom2) + a(3,atom2)*txj + a(6,atom2)*tyj + a(9,atom2)*tzj
752 > #endif    
753 >       ! Now, on to the forces:
754 >
755 >       ! first rotate the i terms back into the lab frame:
756 >
757 >       radcomxi = (v0*s*dwidx+v0p*sp*dwipdx)*sw
758 >       radcomyi = (v0*s*dwidy+v0p*sp*dwipdy)*sw
759 >       radcomzi = (v0*s*dwidz+v0p*sp*dwipdz)*sw
760 >
761 >       radcomxj = (v0*s*dwjdx+v0p*sp*dwjpdx)*sw
762 >       radcomyj = (v0*s*dwjdy+v0p*sp*dwjpdy)*sw
763 >       radcomzj = (v0*s*dwjdz+v0p*sp*dwjpdz)*sw
764 >
765 > #ifdef IS_MPI    
766 >       fxii = a_Row(1,atom1)*(radcomxi) + &
767 >            a_Row(4,atom1)*(radcomyi) + &
768 >            a_Row(7,atom1)*(radcomzi)
769 >       fyii = a_Row(2,atom1)*(radcomxi) + &
770 >            a_Row(5,atom1)*(radcomyi) + &
771 >            a_Row(8,atom1)*(radcomzi)
772 >       fzii = a_Row(3,atom1)*(radcomxi) + &
773 >            a_Row(6,atom1)*(radcomyi) + &
774 >            a_Row(9,atom1)*(radcomzi)
775 >
776 >       fxjj = a_Col(1,atom2)*(radcomxj) + &
777 >            a_Col(4,atom2)*(radcomyj) + &
778 >            a_Col(7,atom2)*(radcomzj)
779 >       fyjj = a_Col(2,atom2)*(radcomxj) + &
780 >            a_Col(5,atom2)*(radcomyj) + &
781 >            a_Col(8,atom2)*(radcomzj)
782 >       fzjj = a_Col(3,atom2)*(radcomxj)+ &
783 >            a_Col(6,atom2)*(radcomyj) + &
784 >            a_Col(9,atom2)*(radcomzj)
785 > #else
786 >       fxii = a(1,atom1)*(radcomxi) + &
787 >            a(4,atom1)*(radcomyi) + &
788 >            a(7,atom1)*(radcomzi)
789 >       fyii = a(2,atom1)*(radcomxi) + &
790 >            a(5,atom1)*(radcomyi) + &
791 >            a(8,atom1)*(radcomzi)
792 >       fzii = a(3,atom1)*(radcomxi) + &
793 >            a(6,atom1)*(radcomyi) + &
794 >            a(9,atom1)*(radcomzi)
795 >
796 >       fxjj = a(1,atom2)*(radcomxj) + &
797 >            a(4,atom2)*(radcomyj) + &
798 >            a(7,atom2)*(radcomzj)
799 >       fyjj = a(2,atom2)*(radcomxj) + &
800 >            a(5,atom2)*(radcomyj) + &
801 >            a(8,atom2)*(radcomzj)
802 >       fzjj = a(3,atom2)*(radcomxj)+ &
803 >            a(6,atom2)*(radcomyj) + &
804 >            a(9,atom2)*(radcomzj)
805 > #endif
806 >
807 >       fxij = -fxii
808 >       fyij = -fyii
809 >       fzij = -fzii
810 >
811 >       fxji = -fxjj
812 >       fyji = -fyjj
813 >       fzji = -fzjj
814 >
815 >       ! now assemble these with the radial-only terms:
816 >
817 >       fxradial = 0.5d0*(v0*dsdr*drdx*w + v0p*dspdr*drdx*wp + fxii + fxji)
818 >       fyradial = 0.5d0*(v0*dsdr*drdy*w + v0p*dspdr*drdy*wp + fyii + fyji)
819 >       fzradial = 0.5d0*(v0*dsdr*drdz*w + v0p*dspdr*drdz*wp + fzii + fzji)
820 >
821 > #ifdef IS_MPI
822 >       f_Row(1,atom1) = f_Row(1,atom1) + fxradial
823 >       f_Row(2,atom1) = f_Row(2,atom1) + fyradial
824 >       f_Row(3,atom1) = f_Row(3,atom1) + fzradial
825 >
826 >       f_Col(1,atom2) = f_Col(1,atom2) - fxradial
827 >       f_Col(2,atom2) = f_Col(2,atom2) - fyradial
828 >       f_Col(3,atom2) = f_Col(3,atom2) - fzradial
829 > #else
830 >       f(1,atom1) = f(1,atom1) + fxradial
831 >       f(2,atom1) = f(2,atom1) + fyradial
832 >       f(3,atom1) = f(3,atom1) + fzradial
833 >
834 >       f(1,atom2) = f(1,atom2) - fxradial
835 >       f(2,atom2) = f(2,atom2) - fyradial
836 >       f(3,atom2) = f(3,atom2) - fzradial
837 > #endif
838 >
839 > #ifdef IS_MPI
840 >       id1 = AtomRowToGlobal(atom1)
841 >       id2 = AtomColToGlobal(atom2)
842 > #else
843 >       id1 = atom1
844 >       id2 = atom2
845 > #endif
846 >
847 >       if (molMembershipList(id1) .ne. molMembershipList(id2)) then
848 >
849 >          fpair(1) = fpair(1) + fxradial
850 >          fpair(2) = fpair(2) + fyradial
851 >          fpair(3) = fpair(3) + fzradial
852 >
853 >       endif
854 >    endif
855 >  end subroutine do_sticky_power_pair
856 >
857 > end module sticky

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines