ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90 (file contents):
Revision 315 by chuckv, Tue Mar 11 20:15:18 2003 UTC vs.
Revision 317 by gezelter, Tue Mar 11 23:13:06 2003 UTC

# Line 1 | Line 1
1   module forceGlobals
2 <
2 >  
3    use definitions
4    use simulation
5    use atype_typedefs
6 <  use generic_lists
6 >  use vector_class
7   #ifdef IS_MPI
8    use mpiSimulation
9   #endif
10 <
11 < !! Number of lj_atypes in lj_atype_list
12 <  integer, save :: n_atypes = 0
13 <
14 < !! Global list of lj atypes in simulation
15 <  type (atype), pointer :: ListHead => null()
16 <  type (atype), pointer :: ListTail => null()
17 <
18 <
19 <
20 <
21 <  logical, save :: firstTime = .True.
22 <
23 < !! Atype identity pointer lists
10 >    
11 >  logical, save :: atype_vector_initialized = .false.
12 >  logical, save :: ff_initialized = .false.
13 >  
14   #ifdef IS_MPI
15 < !! Row lj_atype pointer list
16 <  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
17 < !! Column lj_atype pointer list
18 <  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
15 >  real( kind = dp ), allocatable, dimension(:,:) :: q_Row
16 >  real( kind = dp ), allocatable, dimension(:,:) :: q_Col
17 >  real( kind = dp ), allocatable, dimension(:,:) :: u_l_Row
18 >  real( kind = dp ), allocatable, dimension(:,:) :: u_l_Col
19 >  real( kind = dp ), allocatable, dimension(:,:) :: A_Row
20 >  real( kind = dp ), allocatable, dimension(:,:) :: A_Col
21 >  
22 >  real( kind = dp ), allocatable, dimension(:) :: pot_Row
23 >  real( kind = dp ), allocatable, dimension(:) :: pot_Col
24 >  real( kind = dp ), allocatable, dimension(:) :: pot_Temp
25 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Row
26 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Col
27 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Temp
28 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Row
29 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Col
30 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Temp
31 >  integer, allocatable, dimension(:) :: atid_Row
32 >  integer, allocatable, dimension(:) :: atid_Col
33   #else
34 <  type(identPtrList ), dimension(:), pointer :: identPtrListGlobal => null()
34 >  integer, allocatable, dimension(:) :: atid
35   #endif
36 <
33 <
34 < !! Logical has lj force field module been initialized?
35 <  logical, save :: isFFinit = .false.
36 <
37 < !! Use periodic boundry conditions
38 <  logical :: wrap = .false.
39 <
40 < !! Potential energy global module variables
41 < #ifdef IS_MPI
42 <    real( kind = dp ), allocatable, dimension(:,:) :: q_Row
43 <    real( kind = dp ), allocatable, dimension(:,:) :: q_Col
44 <    real( kind = dp ), allocatable, dimension(:,:) :: u_l_Row
45 <    real( kind = dp ), allocatable, dimension(:,:) :: u_l_Col
46 <    real( kind = dp ), allocatable, dimension(:,:) :: A_Row
47 <    real( kind = dp ), allocatable, dimension(:,:) :: A_Col
48 <
49 <    real( kind = dp ), allocatable, dimension(:) :: pot_Row
50 <    real( kind = dp ), allocatable, dimension(:) :: pot_Col
51 <    real( kind = dp ), allocatable, dimension(:) :: pot_Temp
52 <    real( kind = dp ), allocatable, dimension(:,:) :: f_Row
53 <    real( kind = dp ), allocatable, dimension(:,:) :: f_Col
54 <    real( kind = dp ), allocatable, dimension(:,:) :: f_Temp
55 <    real( kind = dp ), allocatable, dimension(:,:) :: t_Row
56 <    real( kind = dp ), allocatable, dimension(:,:) :: t_Col
57 <    real( kind = dp ), allocatable, dimension(:,:) :: t_Temp
58 < #endif
59 <
36 >  
37    real(kind = dp) :: pot = 0.0_dp
38    real(kind = dp), dimension(9) :: tau_Temp = 0.0_dp
39    real(kind = dp) :: virial_Temp = 0.0_dp
40 <
64 <  logical :: do_preForce  = .false.
65 <  logical :: do_postForce = .false.
66 <
67 <
68 <
69 < !! Public methods and data
40 >  
41    public :: new_atype
42    public :: init_FF
43  
44 + contains
45    
46 +  subroutine new_atype(c_ident, is_LJ, is_Sticky, is_DP, is_GB, &
47 +       lj_epsilon, lj_sigma, &
48 +       dipole_moment, &
49 +       sticky_w0, sticky_v0, &
50 +       GB_sigma, GB_l2b_ratio, GB_eps, GB_eps_ratio, GB_mu, GB_nu, &
51 +       status)
52 +    
53 +    real( kind = dp ), intent(in) :: lj_epsilon
54 +    real( kind = dp ), intent(in) :: lj_sigma
55 +    real( kind = dp ), intent(in) :: sticky_w0
56 +    real( kind = dp ), intent(in) :: sticky_v0
57 +    real( kind = dp ), intent(in) :: dipole_moment
58 +    real( kind = dp ), intent(in) :: GB_sigma, GB_l2b_ratio, GB_eps
59 +    real( kind = dp ), intent(in) :: GB_eps_ratio, GB_mu, GB_nu
60  
61 <
76 < contains
77 <
78 < !! Adds a new lj_atype to the list.
79 <  subroutine new_atype(ident, epsilon, sigma, &
80 <       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
81 <
82 <    real( kind = dp ), intent(in) :: epsilon
83 <    real( kind = dp ), intent(in) :: sigma
84 <    real( kind = dp ), intent(in) :: w0
85 <    real( kind = dp ), intent(in) :: v0
86 <    real( kind = dp ), intent(in) :: dipoleMoment
87 <
88 <    integer, intent(in) :: ident
61 >    integer, intent(in)  :: c_ident
62      integer, intent(out) :: status
63 <    integer, intent(in) :: is_Sticky
64 <    integer, intent(in) :: is_DP
65 <    integer, intent(in) :: is_GB
66 <    integer, intent(in) :: is_LJ
63 >    integer, intent(in)  :: is_Sticky
64 >    integer, intent(in)  :: is_DP
65 >    integer, intent(in)  :: is_GB
66 >    integer, intent(in)  :: is_LJ
67 >    integer :: me
68 >    logical :: l_is_LJ, l_is_DP, l_is_Sticky, l_is_GB
69  
95
96    type (atype), pointer :: the_new_atype
97    integer :: alloc_error
98    integer :: atype_counter = 0
99    integer :: alloc_size
100    integer :: err_stat
70      status = 0
71  
72 +    if (.not.atype_vector_initialized) then
73 +       !! There are 16 properties to worry about for now.  
74 +       !! Fix this if needed for more atomic properties
75 +       atypes = initialize(16)
76 +       if (.not.associated(atypes)) then
77 +          status = -1
78 +          return
79 +       endif
80 +    endif
81  
82 +    me = addElement(atypes)
83  
84 < ! allocate a new atype    
106 <    allocate(the_new_atype,stat=alloc_error)
107 <    if (alloc_error /= 0 ) then
108 <       status = -1
109 <       return
110 <    end if
84 >    call setElementProperty(atypes, me, "c_ident", c_ident)
85  
86 < ! assign our new atype information
86 >    l_is_LJ = (is_LJ .ne. 0)
87 >    l_is_DP = (is_DP .ne. 0)
88 >    l_is_Sticky = (is_Sticky .ne. 0)
89 >    l_is_GB = (is_GB .ne. 0)
90  
91 <    the_new_atype%lj_epsilon     = epsilon
92 <    the_new_atype%lj_sigma       = sigma
93 <    the_new_atype%sticky_w0       = w0
94 <    the_new_atype%sticky_v0       = v0
118 <    the_new_atype%dipole_moment       = dipoleMoment
119 <
120 <    
121 < ! assume that this atype will be successfully added
122 <    the_new_atype%atype_ident = ident
123 <    the_new_atype%atype_fortran_index = atype_count + 1
124 <    
125 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
126 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
127 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
128 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
91 >    call setElementProperty(atypes, me, "is_LJ", l_is_LJ)
92 >    call setElementProperty(atypes, me, "is_DP", l_is_DP)
93 >    call setElementProperty(atypes, me, "is_Sticky", l_is_Sticky)
94 >    call setElementProperty(atypes, me, "is_GB", l_is_GB)
95  
96 <    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
97 <    if (err_stat /= 0 ) then
98 <       status = -1
133 <       return
96 >    if (l_is_LJ) then
97 >       call setElementProperty(atypes, me, "lj_sigma", lj_sigma)
98 >       call setElementProperty(atypes, me, "lj_epsilon", lj_epsilon)
99      endif
100 <    
101 <    atype_count = atype_count + 1
102 <    
103 <    
100 >    if (l_is_DP) then
101 >       call setElementProperty(atypes, me, "dipole_moment", dipole_moment)
102 >    endif
103 >    if (l_is_Sticky) then
104 >       call setElementProperty(atypes, me, "sticky_w0", sticky_w0)
105 >       call setElementProperty(atypes, me, "sticky_v0", sticky_v0)
106 >    endif
107 >    if (l_is_GB) then
108 >       call setElementProperty(atypes, me, "GB_sigma", GB_sigma)
109 >       call setElementProperty(atypes, me, "GB_l2b_ratio", GB_l2b_ratio)
110 >       call setElementProperty(atypes, me, "GB_eps", GB_eps)
111 >       call setElementProperty(atypes, me, "GB_eps_ratio", GB_eps_ratio)
112 >       call setElementProperty(atypes, me, "GB_mu", GB_mu)
113 >       call setElementProperty(atypes, me, "GB_nu", GB_nu)
114 >    endif
115 >
116    end subroutine new_atype
117  
118 <
119 <  subroutine init_FF(nComponents,ident, nExcludes,excludesLocal,status)
120 < !! Number of components in ident array
118 >  
119 >  subroutine init_FF(nComponents, c_idents, nExcludes, excludesLocal, status)
120 >    !! Number of components in c_idents array
121      integer, intent(inout) :: nComponents
122 < !! Array of identities nComponents long corresponding to
123 < !! ljatype ident.
124 <    integer, dimension(nComponents),intent(inout) :: ident
122 >    !! Array of identities nComponents long corresponding to
123 >    !! ljatype ident.
124 >    integer, dimension(nComponents),intent(inout) :: c_idents
125      integer :: nExcludes
126      integer, dimension(nExcludes),intent(inout) :: excludesLocal
127 < !!  Result status, success = 0, error = -1
128 <    integer, intent(out) :: Status
129 <
153 <    integer :: alloc_stat
154 <
155 <    integer :: thisStat
156 <    integer :: i
157 <
127 >    !!  Result status, success = 0, error = -1
128 >    integer, intent(out) :: status    
129 >    integer :: i, me, thisStat
130      integer :: myNode
131 +
132   #ifdef IS_MPI
133 <    integer, allocatable, dimension(:) :: identRow
134 <    integer, allocatable, dimension(:) :: identCol
133 >    integer, allocatable, dimension(:) :: c_idents_Row
134 >    integer, allocatable, dimension(:) :: c_idents_Col
135      integer :: nrow
136      integer :: ncol
137   #endif
138 +
139      status = 0
166  
140  
168    
141  
142 < !! if were're not in MPI, we just update ljatypePtrList
143 < #ifndef IS_MPI
172 <    call create_IdentPtrList(ident,ListHead,identPtrListGlobal,thisStat)
173 <    if ( thisStat /= 0 ) then
174 <       status = -1
175 <       return
176 <    endif
177 <
178 <    
179 < ! if were're in MPI, we also have to worry about row and col lists    
180 < #else
181 <  
182 < ! We can only set up forces if mpiSimulation has been setup.
142 > #ifdef IS_MPI
143 >    ! We can only set up forces if mpiSimulation has been setup.
144      if (.not. isMPISimSet()) then
145         write(default_error,*) "MPI is not set"
146         status = -1
# Line 188 | Line 149 | contains
149      nrow = getNrow(plan_row)
150      ncol = getNcol(plan_col)
151      mynode = getMyNode()
152 < !! Allocate temperary arrays to hold gather information
153 <    allocate(identRow(nrow),stat=alloc_stat)
152 >    
153 >    allocate(c_idents_Row(nrow),stat=alloc_stat)
154      if (alloc_stat /= 0 ) then
155         status = -1
156         return
157      endif
158  
159 <    allocate(identCol(ncol),stat=alloc_stat)
159 >    allocate(c_idents_Col(ncol),stat=alloc_stat)
160      if (alloc_stat /= 0 ) then
161         status = -1
162         return
163      endif
164  
165 < !! Gather idents into row and column idents
166 <
167 <    call gather(ident,identRow,plan_row)
168 <    call gather(ident,identCol,plan_col)
169 <    
209 <  
210 < !! Create row and col pointer lists
211 <  
212 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
213 <    if (thisStat /= 0 ) then
165 >    call gather(c_idents, c_idents_Row, plan_row)
166 >    call gather(c_idents, c_idents_Col, plan_col)
167 >
168 >    allocate(atid_Row(nrow),stat=alloc_stat)
169 >    if (alloc_stat /= 0 ) then
170         status = -1
171         return
172      endif
173 <  
174 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
175 <    if (thisStat /= 0 ) then
173 >
174 >    allocate(atid_Col(ncol),stat=alloc_stat)
175 >    if (alloc_stat /= 0 ) then
176         status = -1
177         return
178      endif
179  
180 < !! free temporary ident arrays
180 >    do i = 1, nrow
181 >       me = getFirstMatchingElement(atypes, "c_ident", c_idents_Row(i))
182 >       atid_Row(i) = me
183 >    enddo
184 >
185 >    do i = 1, ncol
186 >       me = getFirstMatchingElement(atypes, "c_ident", c_idents_Col(i))
187 >       atid_Col(i) = me
188 >    enddo
189 >
190 >    !! free temporary ident arrays
191      if (allocated(identCol)) then
192         deallocate(identCol)
193      end if
194      if (allocated(identCol)) then
195         deallocate(identRow)
196      endif
197 +    
198 + #else
199 +    do i = 1, nComponents
200  
201 +       me = getFirstMatchingElement(atypes, "c_ident", c_idents(i))
202 +       atid(i) = me
203 +
204 +    enddo
205   #endif
206 <    
206 >
207      call initForce_Modules(thisStat)
208      if (thisStat /= 0) then
209         status = -1
210         return
211      endif
212 <
213 < !! Create neighbor lists
212 >    
213 >    !! Create neighbor lists
214      call expandList(thisStat)
215      if (thisStat /= 0) then
216         status = -1
217         return
218      endif
219 <
219 >    
220      call setupGlobals(thisStat)
221      if (thisStat /= 0) then
222         status = -1
223         return
224      endif
252
253    isFFinit = .true.
225      
226 +    ff_initialized = .true.
227      
228 +    
229    end subroutine init_FF
230 <
230 >  
231    subroutine setupGlobals(thisStat)
232      integer, intent(out) :: thisStat
233 <
261 <
233 >    
234    end subroutine setupGlobals
235 <
236 <
235 >  
236 >  
237    subroutine initForce_Modules(thisStat)
238      integer, intent(out) :: thisStat
239      integer :: my_status
240      
241      thisStat = 0
242 <    call init_lj_FF(ListHead,my_status)
242 >    call init_lj_FF(my_status)
243      if (my_status /= 0) then
244         thisStat = -1
245         return
246      end if
247 <
247 >    
248    end subroutine initForce_Modules
249 <
278 <
249 >  
250   end module forceGlobals

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines