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

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

# Line 16 | Line 16 | module charge_charge
16    real(kind=dp), parameter :: pre = 332.06508_DP  
17    logical, save :: haveChargeMap = .false.
18  
19 <  public::do_charge_pair
20 <
19 >  public :: newChargeType
20 >  public :: do_charge_pair
21 >  public :: getCharge
22 >  
23    type :: ChargeList
24 +     integer :: ident
25       real(kind=DP) :: charge = 0.0_DP
26    end type ChargeList
27  
28    type(ChargeList), dimension(:), allocatable :: ChargeMap
29  
30   contains
31 <      
32 <  subroutine createChargeMap(status)
31 >
32 >  subroutine newChargeType(ident, charge, status)
33 >    integer,intent(in) :: ident
34 >    real(kind=dp),intent(in) :: charge
35 >    integer,intent(out) :: status
36      integer :: nAtypes
37 <    integer :: status
32 <    integer :: i
33 <    real (kind=DP) :: thisCharge
34 <    logical :: thisProperty
35 <    
37 >
38      status = 0
39      
40 <    nAtypes = getSize(atypes)
40 >    !! Be simple-minded and assume that we need a ChargeMap that
41 >    !! is the same size as the total number of atom types
42 >
43 >    if (.not.allocated(ChargeMap)) then
44 >      
45 >       nAtypes = getSize(atypes)
46      
47 <    if (nAtypes == 0) then
47 >       if (nAtypes == 0) then
48 >          status = -1
49 >          return
50 >       end if
51 >      
52 >       if (.not. allocated(ChargeMap)) then
53 >          allocate(ChargeMap(nAtypes))
54 >       endif
55 >      
56 >    end if
57 >
58 >    if (ident .gt. size(ChargeMap)) then
59         status = -1
60         return
43    end if
44    
45    if (.not. allocated(ChargeMap)) then
46       allocate(ChargeMap(nAtypes))
61      endif
62 +    
63 +    ! set the values for ChargeMap for this atom type:
64  
65 <    do i = 1, nAtypes
66 <
51 <       call getElementProperty(atypes, i, "is_Charge", thisProperty)
52 <
53 <       if (thisProperty) then
54 <          call getElementProperty(atypes, i, "charge", thisCharge)
55 <          ChargeMap(i)%charge = thisCharge
56 <       endif
57 <      
58 <    end do
65 >    ChargeMap(ident)%ident = ident
66 >    ChargeMap(ident)%charge = charge
67      
68 <    haveChargeMap = .true.
68 >  end subroutine newChargeType
69 >  
70 >  function getCharge(atid) result (c)
71 >    integer, intent(in) :: atid
72 >    integer :: localError
73 >    real(kind=dp) :: c
74      
75 <  end subroutine createChargeMap
75 >    if (.not.allocated(ChargeMap)) then
76 >       call handleError("charge_charge", "no ChargeMap was present before first call of getCharge!")
77 >       return
78 >    end if
79      
80 +    c = ChargeMap(atid)%charge
81 +  end function getCharge
82 +      
83    subroutine do_charge_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
84         pot, f, do_pot)
85      
# Line 76 | Line 95 | contains
95      real( kind = dp ), dimension(3) :: d, fpair
96      real( kind = dp ), dimension(3,nLocal) :: f
97      
79    if (.not.haveChargeMap) then
80       localError = 0
81       call createChargeMap(localError)
82       if ( localError .ne. 0 ) then
83          call handleError("charge-charge", "ChargeMap creation failed!")
84          return
85       end if
86    endif
98  
99 +    if (.not.allocated(ChargeMap)) then
100 +       call handleError("charge_charge", "no ChargeMap was present before first call of do_charge_pair!")
101 +       return
102 +    end if
103 +
104   #ifdef IS_MPI
105      me1 = atid_Row(atom1)
106      me2 = atid_Col(atom2)
# Line 157 | Line 173 | end module charge_charge
173    end subroutine do_charge_pair
174    
175   end module charge_charge
176 +
177 + subroutine newChargeType(ident, charge, status)
178 +
179 +  use charge_charge, ONLY : module_newChargeType => newChargeType
180 +
181 +  integer, parameter :: DP = selected_real_kind(15)
182 +  integer,intent(inout) :: ident
183 +  real(kind=dp),intent(inout) :: charge
184 +  integer,intent(inout) :: status
185 +  
186 +  call module_newChargeType(ident, charge, status)
187 +  
188 + end subroutine newChargeType

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines