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

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/dipole.F90 (file contents):
Revision 1632 by gezelter, Wed Oct 20 04:02:48 2004 UTC vs.
Revision 1633 by gezelter, Fri Oct 22 20:22:48 2004 UTC

# Line 14 | Line 14 | module dipole_dipole
14    PRIVATE
15  
16    real(kind=dp), parameter :: pre = 14.38362_dp
17  logical, save :: haveMomentMap = .false.
17  
18 <  public::do_dipole_pair
18 >  public :: newDipoleType
19 >  public :: do_dipole_pair
20 >  public :: getDipoleMoment
21  
22    type :: MomentList
23 +     integer :: ident
24       real(kind=DP) :: dipole_moment = 0.0_DP
25    end type MomentList
26  
# Line 26 | Line 28 | contains
28  
29   contains
30  
31 <  subroutine createMomentMap(status)
31 >  subroutine newDipoleType(ident, dipole_moment, status)
32 >    integer,intent(in) :: ident
33 >    real(kind=dp),intent(in) :: dipole_moment
34 >    integer,intent(out) :: status
35      integer :: nAtypes
31    integer :: status
32    integer :: i
33    real (kind=DP) :: thisDP
34    logical :: thisProperty
36  
37      status = 0
38 +    
39 +    !! Be simple-minded and assume that we need a MomentMap that
40 +    !! is the same size as the total number of atom types
41  
42 <    nAtypes = getSize(atypes)
42 >    if (.not.allocated(MomentMap)) then
43 >      
44 >       nAtypes = getSize(atypes)
45      
46 <    if (nAtypes == 0) then
46 >       if (nAtypes == 0) then
47 >          status = -1
48 >          return
49 >       end if
50 >      
51 >       if (.not. allocated(MomentMap)) then
52 >          allocate(MomentMap(nAtypes))
53 >       endif
54 >      
55 >    end if
56 >
57 >    if (ident .gt. size(MomentMap)) then
58         status = -1
59         return
43    end if
44    
45    if (.not. allocated(MomentMap)) then
46       allocate(MomentMap(nAtypes))
60      endif
61 +    
62 +    ! set the values for MomentMap for this atom type:
63  
64 <    do i = 1, nAtypes
64 >    MomentMap(ident)%ident = ident
65 >    MomentMap(ident)%dipole_moment = dipole_moment
66 >    
67 >  end subroutine newDipoleType
68  
69 <       call getElementProperty(atypes, i, "is_DP", thisProperty)
70 <
71 <       if (thisProperty) then
72 <          call getElementProperty(atypes, i, "dipole_moment", thisDP)
55 <          MomentMap(i)%dipole_moment = thisDP
56 <       endif
57 <      
58 <    end do
69 >  function getDipoleMoment(atid) result (dm)
70 >    integer, intent(in) :: atid
71 >    integer :: localError
72 >    real(kind=dp) :: dm
73      
74 <    haveMomentMap = .true.
74 >    if (.not.allocated(MomentMap)) then
75 >       call handleError("dipole-dipole", "no MomentMap was present before first call of getDipoleMoment!")
76 >       return
77 >    end if
78      
79 <  end subroutine createMomentMap
80 <  
79 >    dm = MomentMap(atid)%dipole_moment
80 >  end function getDipoleMoment
81 >
82    subroutine do_dipole_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
83         pot, u_l, f, t, do_pot)
84      
# Line 83 | Line 101 | contains
101      real (kind = dp), dimension(3) :: ul1
102      real (kind = dp), dimension(3) :: ul2
103  
86    if (.not.haveMomentMap) then
87       localError = 0
88       call createMomentMap(localError)
89       if ( localError .ne. 0 ) then
90          call handleError("dipole-dipole", "MomentMap creation failed!")
91          return
92       end if
93    endif
104  
105 +    if (.not.allocated(MomentMap)) then
106 +       call handleError("dipole-dipole", "no MomentMap was present before first call of do_dipole_pair!")
107 +       return
108 +    end if
109 +
110 +
111   #ifdef IS_MPI
112      me1 = atid_Row(atom1)
113      ul1(1) = u_l_Row(1,atom1)
# Line 216 | Line 232 | end module dipole_dipole
232    end subroutine do_dipole_pair
233    
234   end module dipole_dipole
235 +
236 + subroutine newDipoleType(ident, dipole_moment, status)
237 +
238 +  use dipole_dipole, ONLY : module_newDipoleType => newDipoleType
239 +
240 +  integer, parameter :: DP = selected_real_kind(15)
241 +  integer,intent(inout) :: ident
242 +  real(kind=dp),intent(inout) :: dipole_moment
243 +  integer,intent(inout) :: status
244 +  
245 +  call module_newDipoleType(ident, dipole_moment, status)
246 +  
247 + end subroutine newDipoleType

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines