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

Comparing trunk/OOPSE/libmdtools/calc_dipole_dipole.F90 (file contents):
Revision 898 by chuckv, Mon Jan 5 22:49:14 2004 UTC vs.
Revision 901 by chuckv, Tue Jan 6 19:49:18 2004 UTC

# Line 5 | Line 5 | module dipole_dipole
5    use atype_module
6    use vector_class
7    use simulation
8 +  use status
9   #ifdef IS_MPI
10    use mpiSimulation
11   #endif
# Line 14 | Line 15 | module dipole_dipole
15    real(kind=dp), save :: rrf = 0.0
16    real(kind=dp), save :: rt  = 0.0
17     real(kind=dp), save :: pre = 0.0
18 <  logical, save :: dipole_initialized = .false.
18 >  logical, save :: haveCutoffs = .false.
19 >  logical, save :: haveMomentMap = .false.
20  
19
21    public::setCutoffsDipole
22    public::do_dipole_pair
23  
24 +  type :: MomentList
25 +     real(kind=DP) :: dipole_moment = 0.0_DP
26 +  end type MomentList
27 +
28 +  type(MomentList), dimension(:),allocatable :: MomentMap
29 +
30   contains
31      
32    subroutine setCutoffsDipole(this_rrf, this_rt)
# Line 30 | Line 37 | contains
37        ! pre converts from mu in units of debye to kcal/mol
38      pre = 14.38362_dp
39  
40 <    dipole_initialized = .true.
40 >    haveCutoffs = .true.
41      
42      return
43    end subroutine setCutoffsDipole
44  
45 +  subroutine createMomentMap(status)
46 +    integer :: nAtypes
47 +    integer :: status
48 +    integer :: i
49 +    real (kind=DP) :: thisDP
50 +    logical :: thisProperty
51 +
52 +    status = 0
53 +
54 +    nAtypes = getSize(atypes)
55 +    
56 +    if (nAtypes == 0) then
57 +       status = -1
58 +       return
59 +    end if
60 +    
61 +    if (.not. allocated(MomentMap)) then
62 +       allocate(MomentMap(nAtypes))
63 +    endif
64 +
65 +    do i = 1, nAtypes
66 +
67 +       call getElementProperty(atypes, i, "is_DP", thisProperty)
68 +
69 +       if (thisProperty) then
70 +          call getElementProperty(atypes, i, "dipole_moment", thisDP)
71 +          MomentMap(i)%dipole_moment = thisDP
72 +       endif
73 +      
74 +    end do
75 +    
76 +    haveMomentMap = .true.
77 +    
78 +  end subroutine createMomentMap
79 +  
80 +  
81    subroutine do_dipole_pair(atom1, atom2, d, rij, r2, pot, u_l, f, t, &
82         do_pot, do_stress)
83      
84      logical :: do_pot, do_stress
85  
86      integer atom1, atom2, me1, me2, id1, id2
87 +    integer :: localError
88      real(kind=dp) :: rij, mu1, mu2
89      real(kind=dp) :: dfact1, dfact2, dip2, r2, r3, r5
90      real(kind=dp) :: dudx, dudy, dudz, dudu1x, dudu1y, dudu1z
# Line 56 | Line 100 | contains
100      real (kind = dp), dimension(3) :: ul1
101      real (kind = dp), dimension(3) :: ul2
102  
103 <    if (.not.dipole_initialized) then
104 <       write(default_error,*) 'Dipole-dipole not initialized!'
103 >    if (.not. haveCutoffs) then
104 >       write(default_error,*) 'Dipole-dipole does not have cutoffs set!'
105         return
106      endif
107 <    
107 >
108 >    if (.not.haveMomentMap) then
109 >       localError = 0
110 >       call createMomentMap(localError)
111 >       if ( localError .ne. 0 ) then
112 >          call handleError("dipole-dipole", "MomentMap creation failed!")
113 >          return
114 >       end if
115 >    endif
116 >
117   #ifdef IS_MPI
118      me1 = atid_Row(atom1)
119      ul1(1) = u_l_Row(1,atom1)
# Line 83 | Line 136 | contains
136      ul2(3) = u_l(3,atom2)
137   #endif
138  
139 +    mu1 = MomentMap(me1)%dipole_moment
140 +    mu2 = MomentMap(me2)%dipole_moment
141  
87    call getElementProperty(atypes, me1, "dipole_moment", mu1)
88    call getElementProperty(atypes, me2, "dipole_moment", mu2)
89
142      if (rij.le.rrf) then
143        
144         if (rij.lt.rt) then
# Line 96 | Line 148 | contains
148            taper = (rrf + 2.0d0*rij - 3.0d0*rt)*(rrf-rij)**2/ ((rrf-rt)**3)
149            dtdr = 6.0d0*(rij*rij - rij*rt - rij*rrf +rrf*rt)/((rrf-rt)**3)
150         endif
151 <
151 >      
152         r3 = r2*rij
153         r5 = r3*r2
154        
155         rdotu1 = d(1)*ul1(1) + d(2)*ul1(2) + d(3)*ul1(3)
156         rdotu2 = d(1)*ul2(1) + d(2)*ul2(2) + d(3)*ul2(3)
157         u1dotu2 = ul1(1)*ul2(1) + ul1(2)*ul2(2) + ul1(3)*ul2(3)
158 <
158 >      
159         dip2 = pre * mu1 * mu2
160         dfact1 = 3.0d0*dip2 / r2
161         dfact2 = 3.0d0*dip2 / r5
162 <
162 >      
163         vterm = dip2*((u1dotu2/r3) - 3.0d0*(rdotu1*rdotu2/r5))
164 <
164 >      
165         if (do_pot) then
166   #ifdef IS_MPI
167            pot_row(atom1) = pot_row(atom1) + 0.5d0*vterm*taper

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines