ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90
Revision: 306
Committed: Mon Mar 10 19:26:45 2003 UTC (21 years, 6 months ago) by chuckv
File size: 7680 byte(s)
Log Message:
More changes to code. Hopefully these will commit smoothly.

File Contents

# User Rev Content
1 chuckv 306 module forceGlobals
2    
3    
4    
5     !! Number of lj_atypes in lj_atype_list
6     integer, save :: n_atypes = 0
7    
8     !! Global list of lj atypes in simulation
9     type (atype), pointer :: ListHead => null()
10     type (atype), pointer :: ListTail => null()
11    
12    
13    
14    
15     logical, save :: firstTime = .True.
16    
17     !! Atype identity pointer lists
18     #ifdef IS_MPI
19     !! Row lj_atype pointer list
20     type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
21     !! Column lj_atype pointer list
22     type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
23     #else
24     type(identPtrList ), dimension(:), pointer :: identPtrList => null()
25     #endif
26    
27    
28     !! Logical has lj force field module been initialized?
29     logical, save :: isFFinit = .false.
30    
31     !! Use periodic boundry conditions
32     logical :: wrap = .false.
33    
34     !! Potential energy global module variables
35     #ifdef IS_MPI
36     real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
37     real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
38    
39     real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
40     real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
41    
42     real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
43     real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
44    
45     real(kind = dp), dimension(9,getNrow(plan_row)) :: ARow = 0.0_dp
46     real(kind = dp), dimension(9,getNcol(plan_col)) :: ACol = 0.0_dp
47    
48     real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
49     real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
50     real(kind = dp), dimension(3,getNlocal()) :: fTemp1 = 0.0_dp
51     real(kind = dp), dimension(3,getNlocal()) :: tTemp1 = 0.0_dp
52     real(kind = dp), dimension(3,getNlocal()) :: fTemp2 = 0.0_dp
53     real(kind = dp), dimension(3,getNlocal()) :: tTemp2 = 0.0_dp
54     real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
55     real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
56    
57     real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
58     real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
59    
60     real(kind = dp), dimension(3,getNrow(plan_row)) :: rflRow = 0.0_dp
61     real(kind = dp), dimension(3,getNcol(plan_col)) :: rflCol = 0.0_dp
62     real(kind = dp), dimension(3,getNlocal()) :: rflTemp = 0.0_dp
63    
64     real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
65     real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
66    
67     real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
68     #endif
69     real(kind = dp) :: pe = 0.0_dp
70     real(kind = dp), dimension(3,natoms) :: fTemp = 0.0_dp
71     real(kind = dp), dimension(3,natoms) :: tTemp = 0.0_dp
72     real(kind = dp), dimension(3,natoms) :: rflTemp = 0.0_dp
73     real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
74    
75     logical :: do_preForce = .false.
76     logical :: do_postForce = .false.
77    
78    
79    
80     !! Public methods and data
81     public :: new_atype
82     public :: do_forceLoop
83     public :: init_FF
84    
85    
86    
87    
88     contains
89    
90     !! Adds a new lj_atype to the list.
91     subroutine new_atype(ident,mass,epsilon,sigma, &
92     is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
93     real( kind = dp ), intent(in) :: mass
94     real( kind = dp ), intent(in) :: epsilon
95     real( kind = dp ), intent(in) :: sigma
96     real( kind = dp ), intent(in) :: w0
97     real( kind = dp ), intent(in) :: v0
98     real( kind = dp ), intent(in) :: dipoleMoment
99    
100     integer, intent(in) :: ident
101     integer, intent(out) :: status
102     integer, intent(in) :: is_Sticky
103     integer, intent(in) :: is_DP
104     integer, intent(in) :: is_GB
105     integer, intent(in) :: is_LJ
106    
107    
108     type (atype), pointer :: the_new_atype
109     integer :: alloc_error
110     integer :: atype_counter = 0
111     integer :: alloc_size
112     integer :: err_stat
113     status = 0
114    
115    
116    
117     ! allocate a new atype
118     allocate(the_new_atype,stat=alloc_error)
119     if (alloc_error /= 0 ) then
120     status = -1
121     return
122     end if
123    
124     ! assign our new atype information
125     the_new_atype%mass = mass
126     the_new_atype%epsilon = epsilon
127     the_new_atype%sigma = sigma
128     the_new_atype%sigma2 = sigma * sigma
129     the_new_atype%sigma6 = the_new_atype%sigma2 * the_new_atype%sigma2 &
130     * the_new_atype%sigma2
131     the_new_atype%w0 = w0
132     the_new_atype%v0 = v0
133     the_new_atype%dipoleMoment = dipoleMoment
134    
135    
136     ! assume that this atype will be successfully added
137     the_new_atype%atype_ident = ident
138     the_new_atype%atype_number = n_lj_atypes + 1
139    
140     if ( is_Sticky /= 0 ) the_new_atype%is_Sticky = .true.
141     if ( is_GB /= 0 ) the_new_atype%is_GB = .true.
142     if ( is_LJ /= 0 ) the_new_atype%is_LJ = .true.
143     if ( is_DP /= 0 ) the_new_atype%is_DP = .true.
144    
145     call add_atype(the_new_atype,ListHead,ListTail,err_stat)
146     if (err_stat /= 0 ) then
147     status = -1
148     return
149     endif
150    
151     n_atypes = n_atypes + 1
152    
153    
154     end subroutine new_atype
155    
156    
157     subroutine init_FF(nComponents,ident, nExcludes,excludesLocal,status)
158     !! Number of components in ident array
159     integer, intent(inout) :: nComponents
160     !! Array of identities nComponents long corresponding to
161     !! ljatype ident.
162     integer, dimension(nComponents),intent(inout) :: ident
163     integer :: nExcludes
164     integer, dimension(n),intent(inout) :: excludesLocal
165     !! Result status, success = 0, error = -1
166     integer, intent(out) :: Status
167    
168     integer :: alloc_stat
169    
170     integer :: thisStat
171     integer :: i
172    
173     integer :: myNode
174     #ifdef IS_MPI
175     integer, allocatable, dimension(:) :: identRow
176     integer, allocatable, dimension(:) :: identCol
177     integer :: nrow
178     integer :: ncol
179     #endif
180     status = 0
181    
182    
183    
184    
185     !! if were're not in MPI, we just update ljatypePtrList
186     #ifndef IS_MPI
187     call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
188     if ( thisStat /= 0 ) then
189     status = -1
190     return
191     endif
192    
193    
194     ! if were're in MPI, we also have to worry about row and col lists
195     #else
196    
197     ! We can only set up forces if mpiSimulation has been setup.
198     if (.not. isMPISimSet()) then
199     write(default_error,*) "MPI is not set"
200     status = -1
201     return
202     endif
203     nrow = getNrow(plan_row)
204     ncol = getNcol(plan_col)
205     mynode = getMyNode()
206     !! Allocate temperary arrays to hold gather information
207     allocate(identRow(nrow),stat=alloc_stat)
208     if (alloc_stat /= 0 ) then
209     status = -1
210     return
211     endif
212    
213     allocate(identCol(ncol),stat=alloc_stat)
214     if (alloc_stat /= 0 ) then
215     status = -1
216     return
217     endif
218    
219     !! Gather idents into row and column idents
220    
221     call gather(ident,identRow,plan_row)
222     call gather(ident,identCol,plan_col)
223    
224    
225     !! Create row and col pointer lists
226    
227     call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
228     if (thisStat /= 0 ) then
229     status = -1
230     return
231     endif
232    
233     call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
234     if (thisStat /= 0 ) then
235     status = -1
236     return
237     endif
238    
239     !! free temporary ident arrays
240     if (allocated(identCol)) then
241     deallocate(identCol)
242     end if
243     if (allocated(identCol)) then
244     deallocate(identRow)
245     endif
246    
247     #endif
248    
249     call initForce_Modules(thisStat)
250     if (thisStat /= 0) then
251     status = -1
252     return
253     endif
254    
255     !! Create neighbor lists
256     call expandList(thisStat)
257     if (thisStat /= 0) then
258     status = -1
259     return
260     endif
261    
262     isFFinit = .true.
263    
264    
265     end subroutine init_FF
266    
267    
268    
269    
270     subroutine initForce_Modules(thisStat)
271     integer, intent(out) :: thisStat
272     integer :: my_status
273    
274     thisStat = 0
275     call init_lj_FF(ListHead,my_status)
276     if (my_status /= 0) then
277     thisStat = -1
278     return
279     end if
280    
281     end subroutine initForce_Modules
282    
283    
284    
285    
286    
287    
288    
289     end module forceGlobals