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

Comparing trunk/OOPSE/libmdtools/calc_charge_charge.F90 (file contents):
Revision 1131 by tim, Thu Apr 22 21:33:55 2004 UTC vs.
Revision 1160 by gezelter, Tue May 11 21:31:15 2004 UTC

# Line 12 | Line 12 | module charge_charge
12    implicit none
13  
14    PRIVATE
15 <  real(kind=dp), save :: ecr = 0.0_DP
16 <  real(kind=dp), save :: rt  = 0.0_DP
17 <  real(kind=dp), save :: pre = 0.0_DP
18 <  logical, save :: haveCutoffs = .false.
15 >
16 >  real(kind=dp), parameter :: pre = 332.06508_DP  
17    logical, save :: haveChargeMap = .false.
18  
21  public::setCutoffsCharge
19    public::do_charge_pair
20  
21    type :: ChargeList
# Line 28 | Line 25 | contains
25    type(ChargeList), dimension(:), allocatable :: ChargeMap
26  
27   contains
28 <    
32 <  subroutine setCutoffsCharge(this_ecr, this_rt)
33 <    real(kind=dp), intent(in) :: this_ecr, this_rt
34 <    ecr = this_ecr
35 <    rt = this_rt
36 <
37 <    ! pre converts from fundamental charge to kcal/mol
38 <    pre = 332.06508_DP
39 <
40 <    haveCutoffs = .true.
41 <    
42 <    return
43 <  end subroutine setCutoffsCharge
44 <
28 >      
29    subroutine createChargeMap(status)
30      integer :: nAtypes
31      integer :: status
# Line 76 | Line 60 | contains
60      haveChargeMap = .true.
61      
62    end subroutine createChargeMap
79  
80  
81  subroutine do_charge_pair(atom1, atom2, d, rij, r2, pot, f, &
82       do_pot, do_stress)
63      
64 +  subroutine do_charge_pair(atom1, atom2, d, rij, r2, sw, vpair, &
65 +       pot, f, do_pot, do_stress)
66 +    
67      logical :: do_pot, do_stress
68  
69      integer atom1, atom2, me1, me2, id1, id2
70      integer :: localError
71 <    real(kind=dp) :: rij, r2, q1, q2
71 >    real(kind=dp) :: rij, r2, q1, q2, sw, vpair
72      real(kind=dp) :: drdx, drdy, drdz, dudr, fx, fy, fz
73 <    real(kind=dp) :: taper, dtdr, vterm
73 >    real(kind=dp) :: vterm
74  
75      real( kind = dp ) :: pot
76      real( kind = dp ), dimension(3) :: d
77      real( kind = dp ), dimension(3,nLocal) :: f
78      
96    if (.not. haveCutoffs) then
97       write(default_error,*) 'charge-charge does not have cutoffs set!'
98       return
99    endif
100
79      if (.not.haveChargeMap) then
80         localError = 0
81         call createChargeMap(localError)
# Line 115 | Line 93 | contains
93      me2 = atid(atom2)
94   #endif
95  
118
96      q1 = ChargeMap(me1)%charge
97      q2 = ChargeMap(me2)%charge
98  
99 <    if (rij.le.ecr) then
123 <      
124 <       if (rij.lt.rt) then
125 <          taper = 1.0d0
126 <          dtdr = 0.0d0
127 <       else
128 <          taper = (ecr + 2.0d0*rij - 3.0d0*rt)*(ecr-rij)**2/ ((ecr-rt)**3)
129 <          dtdr = 6.0d0*(rij*rij - rij*rt - rij*ecr +ecr*rt)/((ecr-rt)**3)
130 <       endif
99 >    vterm = pre * q1 * q2 / rij
100  
101 <       vterm = pre * q1 * q2 / rij
101 >    dudr =  -sw * vterm  / rij
102  
103 <       !!if(rij .le. 1.5) then
104 <       !!  write(*,*) atom1, atom2, q1, q2, rij, vterm
105 <       !!endif
103 >    drdx = d(1) / rij
104 >    drdy = d(2) / rij
105 >    drdz = d(3) / rij
106 >    
107 >    fx = dudr * drdx
108 >    fy = dudr * drdy
109 >    fz = dudr * drdz          
110  
111 <       dudr = vterm * ( dtdr  - taper / rij )
112 <
140 <       drdx = d(1) / rij
141 <       drdy = d(2) / rij
142 <       drdz = d(3) / rij
143 <
144 <       fx = dudr * drdx
145 <       fy = dudr * drdy
146 <       fz = dudr * drdz          
147 <
148 <
111 >    vpair = vpair + vterm
112 >    
113   #ifdef IS_MPI
114 <       if (do_pot) then
115 <          pot_Row(atom1) = pot_Row(atom1) + vterm*taper*0.5
116 <          pot_Col(atom2) = pot_Col(atom2) + vterm*taper*0.5
117 <       endif
118 <
119 <       f_Row(1,atom1) = f_Row(1,atom1) + fx
120 <       f_Row(2,atom1) = f_Row(2,atom1) + fy
121 <       f_Row(3,atom1) = f_Row(3,atom1) + fz
122 <
123 <       f_Col(1,atom2) = f_Col(1,atom2) - fx
124 <       f_Col(2,atom2) = f_Col(2,atom2) - fy
125 <       f_Col(3,atom2) = f_Col(3,atom2) - fz
126 <
114 >    if (do_pot) then
115 >       pot_Row(atom1) = pot_Row(atom1) + sw*vterm*0.5
116 >       pot_Col(atom2) = pot_Col(atom2) + sw*vterm*0.5
117 >    endif
118 >    
119 >    f_Row(1,atom1) = f_Row(1,atom1) + fx
120 >    f_Row(2,atom1) = f_Row(2,atom1) + fy
121 >    f_Row(3,atom1) = f_Row(3,atom1) + fz
122 >    
123 >    f_Col(1,atom2) = f_Col(1,atom2) - fx
124 >    f_Col(2,atom2) = f_Col(2,atom2) - fy
125 >    f_Col(3,atom2) = f_Col(3,atom2) - fz
126 >    
127   #else
128  
129 <       if (do_pot) pot = pot + vterm*taper
130 <
131 <       f(1,atom1) = f(1,atom1) + fx
132 <       f(2,atom1) = f(2,atom1) + fy
133 <       f(3,atom1) = f(3,atom1) + fz
134 <
135 <       f(1,atom2) = f(1,atom2) - fx
136 <       f(2,atom2) = f(2,atom2) - fy
137 <       f(3,atom2) = f(3,atom2) - fz
138 <
129 >    if (do_pot) pot = pot + sw*vterm
130 >    
131 >    f(1,atom1) = f(1,atom1) + fx
132 >    f(2,atom1) = f(2,atom1) + fy
133 >    f(3,atom1) = f(3,atom1) + fz
134 >    
135 >    f(1,atom2) = f(1,atom2) - fx
136 >    f(2,atom2) = f(2,atom2) - fy
137 >    f(3,atom2) = f(3,atom2) - fz
138 >        
139   #endif
140 <
141 <       if (do_stress) then
142 <
140 >    
141 >    if (do_stress) then
142 >      
143   #ifdef IS_MPI
144 <          id1 = tagRow(atom1)
145 <          id2 = tagColumn(atom2)
144 >       id1 = tagRow(atom1)
145 >       id2 = tagColumn(atom2)
146   #else
147 <          id1 = atom1
148 <          id2 = atom2
147 >       id1 = atom1
148 >       id2 = atom2
149   #endif
186
187
188          if (molMembershipList(id1) .ne. molMembershipList(id2)) then
189
190             ! because the d vector is the rj - ri vector, and
191             ! because fx, fy, fz are the force on atom i, we need a
192             ! negative sign here:
193            
194             tau_Temp(1) = tau_Temp(1) - d(1) * fx
195             tau_Temp(2) = tau_Temp(2) - d(1) * fy
196             tau_Temp(3) = tau_Temp(3) - d(1) * fz
197             tau_Temp(4) = tau_Temp(4) - d(2) * fx
198             tau_Temp(5) = tau_Temp(5) - d(2) * fy
199             tau_Temp(6) = tau_Temp(6) - d(2) * fz
200             tau_Temp(7) = tau_Temp(7) - d(3) * fx
201             tau_Temp(8) = tau_Temp(8) - d(3) * fy
202             tau_Temp(9) = tau_Temp(9) - d(3) * fz
203            
204             virial_Temp = virial_Temp + &
205                  (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
206            
207          endif
208       endif
150        
151 +      
152 +       if (molMembershipList(id1) .ne. molMembershipList(id2)) then
153 +          
154 +          ! because the d vector is the rj - ri vector, and
155 +          ! because fx, fy, fz are the force on atom i, we need a
156 +          ! negative sign here:
157 +          
158 +          tau_Temp(1) = tau_Temp(1) - d(1) * fx
159 +          tau_Temp(2) = tau_Temp(2) - d(1) * fy
160 +          tau_Temp(3) = tau_Temp(3) - d(1) * fz
161 +          tau_Temp(4) = tau_Temp(4) - d(2) * fx
162 +          tau_Temp(5) = tau_Temp(5) - d(2) * fy
163 +          tau_Temp(6) = tau_Temp(6) - d(2) * fz
164 +          tau_Temp(8) = tau_Temp(8) - d(3) * fy
165 +          tau_Temp(9) = tau_Temp(9) - d(3) * fz
166 +          
167 +          
168 +          virial_Temp = virial_Temp + &
169 +               (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
170 +          
171 +       endif
172      endif
173 +    
174 +    
175      return
176    end subroutine do_charge_pair
177    

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines