ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90
Revision: 310
Committed: Tue Mar 11 00:40:38 2003 UTC (21 years, 6 months ago) by chuckv
File size: 6797 byte(s)
Log Message:
Changed generic lists so they work correctly

File Contents

# User Rev Content
1 chuckv 306 module forceGlobals
2    
3 gezelter 309 use definitions
4     use simulation
5     use atype_typedefs
6 chuckv 310 use generic_lists
7 gezelter 309 #ifdef IS_MPI
8     use mpiSimulation
9     #endif
10 chuckv 306
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
24     #ifdef IS_MPI
25     !! Row lj_atype pointer list
26     type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
27     !! Column lj_atype pointer list
28     type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
29     #else
30 gezelter 309 type(identPtrList ), dimension(:), pointer :: identPtrListGlobal => null()
31 chuckv 306 #endif
32    
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 gezelter 309 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 chuckv 306
49 gezelter 309 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 chuckv 306
60 gezelter 309 real(kind = dp) :: pot = 0.0_dp
61     real(kind = dp), dimension(9) :: tau_Temp = 0.0_dp
62     real(kind = dp) :: virial_Temp = 0.0_dp
63 chuckv 306
64     logical :: do_preForce = .false.
65     logical :: do_postForce = .false.
66    
67    
68    
69     !! Public methods and data
70     public :: new_atype
71     public :: init_FF
72    
73    
74    
75    
76     contains
77    
78     !! Adds a new lj_atype to the list.
79 gezelter 309 subroutine new_atype(ident, epsilon, sigma, &
80 chuckv 306 is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
81 gezelter 309
82 chuckv 306 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
89     integer, intent(out) :: status
90     integer, intent(in) :: is_Sticky
91     integer, intent(in) :: is_DP
92     integer, intent(in) :: is_GB
93     integer, intent(in) :: is_LJ
94    
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
101     status = 0
102    
103    
104    
105     ! 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
111    
112     ! assign our new atype information
113 gezelter 309
114     the_new_atype%lj_epsilon = epsilon
115     the_new_atype%lj_sigma = sigma
116     the_new_atype%sticky_w0 = w0
117     the_new_atype%sticky_v0 = v0
118     the_new_atype%dipole_moment = dipoleMoment
119 chuckv 306
120    
121     ! assume that this atype will be successfully added
122     the_new_atype%atype_ident = ident
123 gezelter 309 the_new_atype%atype_fortran_index = atype_count + 1
124 chuckv 306
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.
129    
130     call add_atype(the_new_atype,ListHead,ListTail,err_stat)
131     if (err_stat /= 0 ) then
132     status = -1
133     return
134     endif
135 gezelter 309
136     atype_count = atype_count + 1
137    
138    
139 chuckv 306 end subroutine new_atype
140    
141    
142     subroutine init_FF(nComponents,ident, nExcludes,excludesLocal,status)
143     !! Number of components in ident array
144     integer, intent(inout) :: nComponents
145     !! Array of identities nComponents long corresponding to
146     !! ljatype ident.
147     integer, dimension(nComponents),intent(inout) :: ident
148     integer :: nExcludes
149 gezelter 309 integer, dimension(nExcludes),intent(inout) :: excludesLocal
150 chuckv 306 !! Result status, success = 0, error = -1
151     integer, intent(out) :: Status
152    
153     integer :: alloc_stat
154    
155     integer :: thisStat
156     integer :: i
157    
158     integer :: myNode
159     #ifdef IS_MPI
160     integer, allocatable, dimension(:) :: identRow
161     integer, allocatable, dimension(:) :: identCol
162     integer :: nrow
163     integer :: ncol
164     #endif
165     status = 0
166    
167    
168    
169    
170     !! if were're not in MPI, we just update ljatypePtrList
171     #ifndef IS_MPI
172 gezelter 309 call create_IdentPtrList(ident,ListHead,identPtrListGlobal,thisStat)
173 chuckv 306 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.
183     if (.not. isMPISimSet()) then
184     write(default_error,*) "MPI is not set"
185     status = -1
186     return
187     endif
188     nrow = getNrow(plan_row)
189     ncol = getNcol(plan_col)
190     mynode = getMyNode()
191     !! Allocate temperary arrays to hold gather information
192     allocate(identRow(nrow),stat=alloc_stat)
193     if (alloc_stat /= 0 ) then
194     status = -1
195     return
196     endif
197    
198     allocate(identCol(ncol),stat=alloc_stat)
199     if (alloc_stat /= 0 ) then
200     status = -1
201     return
202     endif
203    
204     !! Gather idents into row and column idents
205    
206     call gather(ident,identRow,plan_row)
207     call gather(ident,identCol,plan_col)
208    
209    
210     !! Create row and col pointer lists
211    
212     call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
213     if (thisStat /= 0 ) then
214     status = -1
215     return
216     endif
217    
218     call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
219     if (thisStat /= 0 ) then
220     status = -1
221     return
222     endif
223    
224     !! free temporary ident arrays
225     if (allocated(identCol)) then
226     deallocate(identCol)
227     end if
228     if (allocated(identCol)) then
229     deallocate(identRow)
230     endif
231    
232     #endif
233    
234     call initForce_Modules(thisStat)
235     if (thisStat /= 0) then
236     status = -1
237     return
238     endif
239    
240     !! Create neighbor lists
241     call expandList(thisStat)
242     if (thisStat /= 0) then
243     status = -1
244     return
245     endif
246    
247     isFFinit = .true.
248 gezelter 309
249    
250 chuckv 306 end subroutine init_FF
251 gezelter 309
252 chuckv 306
253    
254     subroutine initForce_Modules(thisStat)
255     integer, intent(out) :: thisStat
256     integer :: my_status
257    
258     thisStat = 0
259     call init_lj_FF(ListHead,my_status)
260     if (my_status /= 0) then
261     thisStat = -1
262     return
263     end if
264    
265     end subroutine initForce_Modules
266    
267    
268     end module forceGlobals