ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
(Generate patch)

Comparing trunk/mdtools/md_code/lj_FF.F90 (file contents):
Revision 232 by chuckv, Fri Jan 10 17:27:28 2003 UTC vs.
Revision 260 by chuckv, Fri Jan 31 21:04:27 2003 UTC

# Line 1 | Line 1
1 + !! Calculates Long Range forces Lennard-Jones interactions.
2 + !! Corresponds to the force field defined in lj_FF.cpp
3 + !! @author Charles F. Vardeman II
4 + !! @author Matthew Meineke
5 + !! @version $Id: lj_FF.F90,v 1.16 2003-01-31 21:04:27 chuckv Exp $, $Date: 2003-01-31 21:04:27 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
6 +
7 +
8 +
9   module lj_ff
10    use simulation
11 <  use definitions, ONLY : dp, ndim
11 >  use definitions
12 >  use generic_atypes
13   #ifdef IS_MPI
14    use mpiSimulation
15   #endif
# Line 10 | Line 19 | module lj_ff
19   !! Number of lj_atypes in lj_atype_list
20    integer, save :: n_lj_atypes = 0
21  
22 < !! Starting Size for ljMixed Array
23 <  integer, parameter :: ljMixed_blocksize = 10
22 > !! Global list of lj atypes in simulation
23 >  type (lj_atype), pointer :: ljListHead => null()
24 >  type (lj_atype), pointer :: ljListTail => null()
25  
16  type, public :: lj_atype
17     private
18     sequence
19 !! Unique number for place in linked list
20     integer :: atype_number = 0
21 !! Unique indentifier number (ie atomic no, etc)
22     integer :: atype_ident = 0
23 !! Mass of Particle
24     real ( kind = dp )  :: mass = 0.0_dp
25 !! Lennard-Jones epslon
26     real ( kind = dp )  :: epslon = 0.0_dp
27 !! Lennard-Jones Sigma
28     real ( kind = dp )  :: sigma = 0.0_dp
29 !! Lennard-Jones Sigma Squared
30     real ( kind = dp )  :: sigma2 = 0.0_dp
31 !! Lennard-Jones Sigma to sixth
32     real ( kind = dp )  :: sigma6 = 0.0_dp
33 !! Pointer for linked list creation
34     type (lj_atype), pointer :: next => null()
35  end type lj_atype
26  
37 !! Pointer type for atype ident array
38  type, public :: lj_atypePtr
39     type (lj_atype), pointer :: this => null()
40  end type lj_atypePtr
41
42 !! Global list of lj atypes in simulation
43  type (lj_atype), pointer :: lj_atype_list => null()
27   !! LJ mixing array  
28 <  type (lj_atype), dimension(:,:), allocatable, pointer :: ljMixed =>null()
46 < !! identity pointer list for force loop.
47 <  type (lj_atypePtr), dimension(:), allocatable :: identPtrList
28 >  type (lj_atype), dimension(:,:), pointer :: ljMixed => null()
29  
30  
31   !! Neighbor list and commom arrays
32 + !! This should eventally get moved to a neighbor list type
33    integer, allocatable, dimension(:) :: point
34    integer, allocatable, dimension(:) :: list
35 +  integer, parameter :: listMultiplier = 80
36 +  integer :: nListAllocs = 0
37 +  integer, parameter :: maxListAllocs = 5
38  
39 < #ifdef IS_MPI
55 < ! Universal routines: All types of force calculations will need these arrays
56 < ! Arrays specific to a type of force calculation should be declared in that module.
57 <  real( kind = dp ), allocatable, dimension(:,:) :: qRow
58 <  real( kind = dp ), allocatable, dimension(:,:) :: qColumn
39 >  logical, save :: firstTime = .True.
40  
41 <  real( kind = dp ), allocatable, dimension(:,:) :: fRow
42 <  real( kind = dp ), allocatable, dimension(:,:) :: fColumn
41 > !! Atype identity pointer lists
42 > #ifdef IS_MPI
43 > !! Row lj_atype pointer list
44 >  type (lj_identPtrList), dimension(:), pointer :: identPtrListRow => null()
45 > !! Column lj_atype pointer list
46 >  type (lj_identPtrList), dimension(:), pointer :: identPtrListColumn => null()
47 > #else
48 >  type( lj_identPtrList ), dimension(:), pointer :: identPtrList => null()
49   #endif
50  
51  
52 + !! Logical has lj force field module been initialized?
53 +  logical, save :: isljFFinit = .false.
54  
55  
67
68
56   !! Public methods and data
57    public :: new_lj_atype
58    public :: do_lj_ff
59    public :: getLjPot
60 <  
60 >  public :: init_ljFF
61  
62    
63  
64  
65   contains
66  
67 <  subroutine new_lj_atype(ident,mass,epslon,sigma,status)
67 > !! Adds a new lj_atype to the list.
68 >  subroutine new_lj_atype(ident,mass,epsilon,sigma,status)
69      real( kind = dp ), intent(in) :: mass
70 <    real( kind = dp ), intent(in) :: epslon
70 >    real( kind = dp ), intent(in) :: epsilon
71      real( kind = dp ), intent(in) :: sigma
72      integer, intent(in) :: ident
73      integer, intent(out) :: status
74  
75 <    type (lj_atype), pointer :: this_lj_atype
88 <    type (lj_atype), pointer :: lj_atype_ptr
89 <
90 <    type (lj_atype), allocatable, dimension(:,:), pointer :: thisMix
91 <    type (lj_atype), allocatable, dimension(:,:), pointer :: oldMix
75 >    type (lj_atype), pointer :: newLJ_atype
76      integer :: alloc_error
77      integer :: atype_counter = 0
78      integer :: alloc_size
79 <
79 >    integer :: err_stat
80      status = 0
81  
82  
83  
84   ! allocate a new atype    
85 <    allocate(this_lj_atype,stat=alloc_error)
85 >    allocate(newLJ_atype,stat=alloc_error)
86      if (alloc_error /= 0 ) then
87         status = -1
88         return
89      end if
90  
91   ! assign our new lj_atype information
92 <    this_lj_atype%mass       = mass
93 <    this_lj_atype%epslon     = epslon
94 <    this_lj_atype%sigma      = sigma
95 <    this_lj_atype%sigma2     = sigma * sigma
96 <    this_lj_atype%sigma6     = this_lj_atype%sigma2 * this_lj_atype%sigma2 &
97 <         * this_lj_atype%sigma2
92 >    newLJ_atype%mass        = mass
93 >    newLJ_atype%epsilon     = epsilon
94 >    newLJ_atype%sigma       = sigma
95 >    newLJ_atype%sigma2      = sigma * sigma
96 >    newLJ_atype%sigma6      = newLJ_atype%sigma2 * newLJ_atype%sigma2 &
97 >         * newLJ_atype%sigma2
98   ! assume that this atype will be successfully added
99 <    this_lj_atype%atype_ident = ident
100 <    this_lj_atype%number = n_lj_atypes + 1
99 >    newLJ_atype%atype_ident = ident
100 >    newLJ_atype%atype_number = n_lj_atypes + 1
101  
102 <
103 < ! First time through allocate a array of size ljMixed_blocksize
104 <    if(.not. associated(ljMixed)) then
105 <       allocate(thisMix(ljMixed_blocksize,ljMixed_blocksize))
122 <       if (alloc_error /= 0 ) then
123 <          status = -1
124 <          return
125 <       end if
126 <       ljMixed => thisMix
127 < ! If we have outgrown ljMixed_blocksize, allocate a new matrix twice the size and
128 < ! point ljMix at the new matrix.
129 <    else if( (n_lj_atypes + 1) > size(ljMixed)) then
130 <       alloc_size = 2*size(ljMix)
131 <       allocate(thisMix(alloc_size,alloc_size))
132 <       if (alloc_error /= 0 ) then
133 <          status = -1
134 <          return
135 <       end if
136 < ! point oldMix at old ljMixed array
137 <       oldMix => ljMixed
138 < ! Copy oldMix into new Mixed array      
139 <       thisMix = oldMix
140 < ! Point ljMixed at new array
141 <       ljMixed => thisMix
142 < ! Free old array so we don't have a memory leak
143 <       deallocate(oldMix)
102 >    call add_atype(newLJ_atype,ljListHead,ljListTail,err_stat)
103 >    if (err_stat /= 0 ) then
104 >       status = -1
105 >       return
106      endif
107  
108 +    n_lj_atypes = n_lj_atypes + 1
109  
110  
111 +  end subroutine new_lj_atype
112  
113  
114 < ! Find bottom of atype master list
115 < ! if lj_atype_list is null then we are at the top of the list.
116 <    if (.not. associated(lj_atype_list)) then
117 <       lj_atype_ptr => this_lj_atype
118 <       atype_counter = 1
114 >  subroutine init_ljFF(nComponents,ident, status)
115 > !! Number of components in ident array
116 >    integer, intent(inout) :: nComponents
117 > !! Array of identities nComponents long corresponding to
118 > !! ljatype ident.
119 >    integer, dimension(nComponents),intent(inout) :: ident
120 > !!  Result status, success = 0, error = -1
121 >    integer, intent(out) :: Status
122  
123 <    else ! we need to find the bottom of the list to insert new atype
157 <       lj_atype_ptr => lj_atype_list%next
158 <       atype_counter = 1
159 <       find_end: do
160 <          if (.not. associated(lj_atype_ptr%next)) then
161 <             exit find_end
162 <          end if
163 < ! Set up mixing for new atype and current atype in list
164 <       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma  =  &
165 <            calcLJMix("sigma",this_lj_atype%sigma, &
166 <            lj_atype_prt%sigma)
123 >    integer :: alloc_stat
124  
125 <       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2  = &
126 <            ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma &
170 <            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma
125 >    integer :: thisStat
126 >    integer :: i
127  
128 <       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma6 = &
129 <            ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
130 <            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
131 <            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2
128 >    integer :: myNode
129 > #ifdef IS_MPI
130 >    integer, allocatable, dimension(:) :: identRow
131 >    integer, allocatable, dimension(:) :: identCol
132 >    integer :: nrow
133 >    integer :: ncol
134 > #endif
135 >    status = 0
136 >  
137  
138 <       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%epslon = &
178 <            calcLJMix("epslon",this_lj_atype%epslon, &
179 <            lj_atype_prt%epslon)
138 >    
139  
140 < ! Advance to next pointer
141 <       lj_atype_ptr => lj_atype_ptr%next
142 <       atype_counter = atype_counter + 1
143 <          
144 <       end do find_end
145 <    end if
140 > !! if were're not in MPI, we just update ljatypePtrList
141 > #ifndef IS_MPI
142 >    call create_IdentPtrlst(ident,ljListHead,identPtrList,thisStat)
143 >    if ( thisStat /= 0 ) then
144 >       status = -1
145 >       return
146 >    endif
147 >
148 > !! Allocate pointer lists
149 >    allocate(point(nComponents),stat=alloc_stat)
150 >    if (alloc_stat /=0) then
151 >       status = -1
152 >       return
153 >    endif
154  
155 +    allocate(list(nComponents*listMultiplier),stat=alloc_stat)
156 +    if (alloc_stat /=0) then
157 +       status = -1
158 +       return
159 +    endif
160 +    
161 + ! if were're in MPI, we also have to worry about row and col lists    
162 + #else
163 +  
164 + ! We can only set up forces if mpiSimulation has been setup.
165 +    if (.not. isMPISimSet()) then
166 +       write(default_error,*) "MPI is not set"
167 +       status = -1
168 +       return
169 +    endif
170 +    nrow = getNrow(plan_row)
171 +    ncol = getNcol(plan_col)
172 +    mynode = getMyNode()
173 + !! Allocate temperary arrays to hold gather information
174 +    allocate(identRow(nrow),stat=alloc_stat)
175 +    if (alloc_stat /= 0 ) then
176 +       status = -1
177 +       return
178 +    endif
179  
180 +    allocate(identCol(ncol),stat=alloc_stat)
181 +    if (alloc_stat /= 0 ) then
182 +       status = -1
183 +       return
184 +    endif
185  
186 + !! Gather idents into row and column idents
187 +
188 +    call gather(ident,identRow,plan_row)
189 +    call gather(ident,identCol,plan_col)
190      
191 < ! Insert new atype at end of list
192 <    lj_atype_ptr => this_lj_atype
193 < ! Increment number of atypes
191 >  
192 > !! Create row and col pointer lists
193 >  
194 >    call create_IdentPtrlst(identRow,ljListHead,identPtrListRow,thisStat)
195 >    if (thisStat /= 0 ) then
196 >       status = -1
197 >       return
198 >    endif
199 >  
200 >    call create_IdentPtrlst(identCol,ljListHead,identPtrListColumn,thisStat)
201 >    if (thisStat /= 0 ) then
202 >       status = -1
203 >       return
204 >    endif
205  
206 <    n_lj_atypes = n_lj_atypes + 1
206 > !! free temporary ident arrays
207 >    if (allocated(identCol)) then
208 >       deallocate(identCol)
209 >    end if
210 >    if (allocated(identCol)) then
211 >       deallocate(identRow)
212 >    endif
213  
214 < ! Set up self mixing
214 > !! Allocate neighbor lists for mpi simulations.
215 >    if (.not. allocated(point)) then
216 >       allocate(point(nrow),stat=alloc_stat)
217 >       if (alloc_stat /=0) then
218 >          status = -1
219 >          return
220 >       endif
221  
222 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma  = this_lj_atype%sigma
222 >       allocate(list(ncol*listMultiplier),stat=alloc_stat)
223 >       if (alloc_stat /=0) then
224 >          status = -1
225 >          return
226 >       endif
227 >    else
228 >       deallocate(list)
229 >       deallocate(point)
230 >       allocate(point(nrow),stat=alloc_stat)
231 >       if (alloc_stat /=0) then
232 >          status = -1
233 >          return
234 >       endif
235  
236 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma2  = ljMix(n_lj_atypes,n_lj_atypes)%sigma &
237 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma
236 >       allocate(list(ncol*listMultiplier),stat=alloc_stat)
237 >       if (alloc_stat /=0) then
238 >          status = -1
239 >          return
240 >       endif
241 >    endif
242  
243 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma6 = ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
244 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
245 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2
243 > #endif
244 >    
245 >    call createMixingList(thisStat)
246 >    if (thisStat /= 0) then
247 >       status = -1
248 >       return
249 >    endif
250 >    isljFFinit = .true.
251  
252 <    ljMix(n_lj_atypes,n_lj_atypes)%epslon = this_lj_atype%epslon
252 >    write(*,*) "Successfully initialized ljFF"
253 >  end subroutine init_ljFF
254  
255  
211  end subroutine new_lj_atype
256  
257  
214  subroutine init_ljFF()
258  
259  
260 < #ifdef IS_MPI
260 >  subroutine createMixingList(status)
261 >    integer :: listSize
262 >    integer :: status
263 >    integer :: i
264 >    integer :: j
265  
266 <    
266 >    integer :: outerCounter = 0
267 >    integer :: innerCounter = 0
268 >    type (lj_atype), pointer :: tmpPtrOuter => null()
269 >    type (lj_atype), pointer :: tmpPtrInner => null()
270 >    status = 0
271  
272 < #endif
272 >    listSize = getListLen(ljListHead)
273 >    if (listSize == 0) then
274 >       status = -1
275 >       return
276 >    end if
277 >  
278  
279 <  end subroutine init_ljFF
279 >    if (.not. associated(ljMixed)) then
280 >       allocate(ljMixed(listSize,listSize))
281 >    else
282 >       status = -1
283 >       return
284 >    end if
285  
286 < !! Takes an ident array and creates an atype pointer list
226 < !! based on those identities
227 <  subroutine new_ljatypePtrList(mysize,ident,PtrList,status)
228 <    integer, intent(in) :: mysize
229 <    integer, intent(in) :: ident
230 <    integer, optional :: status
231 <    type(lj_atypePtr), dimension(:) :: PtrList
286 >    
287  
288 <    integer :: thisIdent
289 <    integer :: i
290 <    integer :: alloc_error
291 <    type (lj_atype), pointer :: tmpPtr
288 >    tmpPtrOuter => ljListHead
289 >    tmpPtrInner => tmpPtrOuter%next
290 >    do while (associated(tmpPtrOuter))
291 >       outerCounter = outerCounter + 1
292 > ! do self mixing rule
293 >       ljMixed(outerCounter,outerCounter)%sigma  = tmpPtrOuter%sigma
294 >                                                                                                  
295 >       ljMixed(outerCounter,outerCounter)%sigma2  = ljMixed(outerCounter,outerCounter)%sigma &
296 >            * ljMixed(outerCounter,outerCounter)%sigma
297 >                                                                                                  
298 >       ljMixed(outerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,outerCounter)%sigma2 &
299 >            * ljMixed(outerCounter,outerCounter)%sigma2 &
300 >            * ljMixed(outerCounter,outerCounter)%sigma2
301 >                                                                                                  
302 >       ljMixed(outerCounter,outerCounter)%epsilon = tmpPtrOuter%epsilon
303  
304 <    if (present(status)) status = 0
305 <
306 < ! First time through, allocate list
307 <    if (.not.(allocated)) then
308 <       allocate(PtrList(mysize))
309 <    else
310 < ! We want to creat a new ident list so free old list
311 <       deallocate(PrtList)
312 <       allocate(PtrList(mysize))
313 <    endif
314 <
315 < ! Match pointer list
316 <    do i = 1, mysize
317 <       thisIdent = ident(i)
318 <       call getLJatype(thisIdent,tmpPtr)
319 <
320 <      if (.not. associated(tmpPtr)) then
321 <          status = -1
322 <          return
304 >       innerCounter = outerCounter + 1
305 >       do while (associated(tmpPtrInner))
306 >          
307 >          ljMixed(outerCounter,innerCounter)%sigma  =  &
308 >               calcLJMix("sigma",tmpPtrOuter%sigma, &
309 >               tmpPtrInner%sigma)
310 >          
311 >          ljMixed(outerCounter,innerCounter)%sigma2  = &
312 >               ljMixed(outerCounter,innerCounter)%sigma &
313 >               * ljMixed(outerCounter,innerCounter)%sigma
314 >          
315 >          ljMixed(outerCounter,innerCounter)%sigma6 = &
316 >               ljMixed(outerCounter,innerCounter)%sigma2 &
317 >               * ljMixed(outerCounter,innerCounter)%sigma2 &
318 >               * ljMixed(outerCounter,innerCounter)%sigma2
319 >          
320 >          ljMixed(outerCounter,innerCounter)%epsilon = &
321 >               calcLJMix("epsilon",tmpPtrOuter%epsilon, &
322 >               tmpPtrInner%epsilon)
323 >          ljMixed(innerCounter,outerCounter)%sigma = ljMixed(outerCounter,innerCounter)%sigma
324 >          ljMixed(innerCounter,outerCounter)%sigma2 = ljMixed(outerCounter,innerCounter)%sigma2
325 >          ljMixed(innerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,innerCounter)%sigma6
326 >          ljMixed(innerCounter,outerCounter)%epsilon = ljMixed(outerCounter,innerCounter)%epsilon
327 >
328 >
329 >          tmpPtrInner => tmpPtrInner%next
330 >          innerCounter = innerCounter + 1
331 >       end do
332 > ! advance pointers
333 >       tmpPtrOuter => tmpPtrOuter%next
334 >       if (associated(tmpPtrOuter)) then
335 >          tmpPtrInner => tmpPtrOuter%next
336         endif
337        
259       PtrList(i)%this => tmpPtr
338      end do
339  
340 <  end subroutine new_ljatypePtrList
340 >  end subroutine createMixingList
341  
264 !! Finds a lj_atype based upon numerical ident
265 !! returns a null pointer if error
266  subroutine getLJatype(ident,ljAtypePtr)
267    integer, intent(in) :: ident
268    type (lj_atype), intent(out),pointer :: ljAtypePtr => null()
269    
270    type (lj_atype), pointer :: tmplj_atype_ptr => null()
342  
272    if(.not. associated(lj_atype_list)) return
343  
274 ! Point at head of list.
275    tmplj_atype_ptr => lj_atype_list
276    find_ident: do
277       if (.not.associated(tmplj_atype_ptr)) then
278          exit find_ident
279       else if( lj_atype_ptr%atype_ident == ident)
280          ljAtypePtr => tmplj_atype_ptr
281          exit find_ident
282       endif
283       tmplj_atype_ptr => tmplj_atype_ptr%next
284    end do find_ident
344  
286  end subroutine getLJatype
345  
346  
347 < ! FORCE routine
347 >
348 >
349 > !! FORCE routine Calculates Lennard Jones forces.
350   !------------------------------------------------------------->
351    subroutine do_lj_ff(q,f,potE,do_pot)
352 <    real ( kind = dp ), dimension(ndim,) :: q
353 <    real ( kind = dp ), dimension(ndim,nLRparticles) :: f
352 > !! Position array provided by C, dimensioned by getNlocal
353 >    real ( kind = dp ), dimension(3,getNlocal()) :: q
354 > !! Force array provided by C, dimensioned by getNlocal
355 >    real ( kind = dp ), dimension(3,getNlocal()) :: f
356      real ( kind = dp ) :: potE
357 <    logical            :: do_pot
358 < #ifdef MPI
359 <  real( kind = DP ), dimension(3,ncol) :: efr
357 >    logical ( kind = 2) :: do_pot
358 >    
359 >    type(lj_atype), pointer :: ljAtype_i
360 >    type(lj_atype), pointer :: ljAtype_j
361 >
362 > #ifdef IS_MPI
363 >  real( kind = DP ), dimension(3,getNcol(plan_col)) :: efr
364    real( kind = DP ) :: pot_local
365   #else
366 < !  real( kind = DP ), dimension(3,natoms) :: efr
366 >  real( kind = DP ), dimension(3,getNlocal()) :: efr
367   #endif
368    
369 + !! Local arrays needed for MPI
370 + #ifdef IS_MPI
371 +  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow
372 +  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol
373 +
374 +  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow
375 +  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol
376 +  real(kind = dp), dimension(3,getNlocal()) :: fMPITemp
377 +
378 +  real(kind = dp), dimension(getNrow(plan_row)) :: eRow
379 +  real(kind = dp), dimension(getNcol(plan_col)) :: eCol
380 +
381 +  real(kind = dp), dimension(getNlocal()) :: eTemp
382 + #endif
383 +
384 +
385 +
386    real( kind = DP )   :: pe
387 <  logical,            :: update_nlist
387 >  logical             :: update_nlist
388  
389  
390    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
# Line 310 | Line 393 | contains
393    integer :: tag_i,tag_j
394    real( kind = DP ) ::  r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
395    real( kind = DP ) ::  rxi, ryi, rzi, rxij, ryij, rzij, rijsq
396 +  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
397  
398 + ! a rig that need to be fixed.
399 + #ifdef IS_MPI
400 +  logical :: newtons_thrd = .true.
401 +  real( kind = dp ) :: pe_local
402 +  integer :: nlocal
403 + #endif
404    integer :: nrow
405    integer :: ncol
406 +  integer :: natoms
407  
408  
409  
410 +
411 + ! Make sure we are properly initialized.
412 +  if (.not. isljFFInit) then
413 +     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
414 +     return
415 +  endif
416 + #ifdef IS_MPI
417 +    if (.not. isMPISimSet()) then
418 +     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
419 +     return
420 +  endif
421 + #endif
422 +
423 + !! initialize local variables  
424 +  natoms = getNlocal()
425 +  call getRcut(rcut,rcut2=rcutsq)
426 +  call getRlist(rlist,rlistsq)
427 +
428   #ifndef IS_MPI
429    nrow = natoms - 1
430    ncol = natoms
431   #else
432 +  nrow = getNrow(plan_row)
433 +  ncol = getNcol(plan_col)
434 +  nlocal = natoms
435    j_start = 1
436   #endif
437  
438 <  call check(update_nlist)
438 >  
439 > !! See if we need to update neighbor lists
440 >  call check(q,update_nlist)
441 >  if (firstTime) then
442 >     update_nlist = .true.
443 >     firstTime = .false.
444 >  endif
445  
446 + !--------------WARNING...........................
447 + ! Zero variables, NOTE:::: Forces are zeroed in C
448 + ! Zeroing them here could delete previously computed
449 + ! Forces.
450 + !------------------------------------------------
451   #ifndef IS_MPI
452 <  nloops = nloops + 1
453 <  pot = 0.0E0_DP
454 <  f = 0.0E0_DP
332 <  e = 0.0E0_DP
452 > !  nloops = nloops + 1
453 >  pe = 0.0E0_DP
454 >
455   #else
456 <    f_row = 0.0E0_DP
457 <    f_col = 0.0E0_DP
456 >    fRow = 0.0E0_DP
457 >    fCol = 0.0E0_DP
458  
459 <    pot_local = 0.0E0_DP
459 >    pe_local = 0.0E0_DP
460  
461 <    e_row = 0.0E0_DP
462 <    e_col = 0.0E0_DP
463 <    e_tmp = 0.0E0_DP
461 >    eRow = 0.0E0_DP
462 >    eCol = 0.0E0_DP
463 >    eTemp = 0.0E0_DP
464   #endif
465      efr = 0.0E0_DP
466 <
466 >    write(*,*) "At first gather of positions"
467   ! communicate MPI positions
468 < #ifdef MPI    
469 <    call gather(q,q_row,plan_row3)
470 <    call gather(q,q_col,plan_col3)
468 > #ifdef IS_MPI    
469 >    call gather(q,qRow,plan_row3d)
470 >    call gather(q,qCol,plan_col3d)
471   #endif
472 +    write(*,*) "Completed gather"
473  
351 #ifndef MPI
352
353 #endif
354
474    if (update_nlist) then
475  
476       ! save current configuration, contruct neighbor list,
477       ! and calculate forces
478 <     call save_nlist()
478 >     call save_nlist(q)
479      
480       nlist = 0
481      
482 <    
482 >    
483  
484       do i = 1, nrow
485          point(i) = nlist + 1
486 < #ifdef MPI
487 <        tag_i = tag_row(i)
488 <        rxi = q_row(1,i)
489 <        ryi = q_row(2,i)
490 <        rzi = q_row(3,i)
486 > #ifdef IS_MPI
487 >        ljAtype_i => identPtrListRow(i)%this
488 >        tag_i = tagRow(i)
489 >        rxi = qRow(1,i)
490 >        ryi = qRow(2,i)
491 >        rzi = qRow(3,i)
492   #else
493 +        ljAtype_i   => identPtrList(i)%this
494          j_start = i + 1
495          rxi = q(1,i)
496          ryi = q(2,i)
# Line 377 | Line 498 | contains
498   #endif
499  
500          inner: do j = j_start, ncol
501 < #ifdef MPI
502 <           tag_j = tag_col(j)
501 > #ifdef IS_MPI
502 > ! Assign identity pointers and tags
503 >           ljAtype_j => identPtrListColumn(j)%this
504 >           tag_j = tagColumn(j)
505             if (newtons_thrd) then
506                if (tag_i <= tag_j) then
507                   if (mod(tag_i + tag_j,2) == 0) cycle inner
# Line 387 | Line 510 | contains
510                endif
511             endif
512  
513 <           rxij = wrap(rxi - q_col(1,j), 1)
514 <           ryij = wrap(ryi - q_col(2,j), 2)
515 <           rzij = wrap(rzi - q_col(3,j), 3)
513 >           rxij = wrap(rxi - qCol(1,j), 1)
514 >           ryij = wrap(ryi - qCol(2,j), 2)
515 >           rzij = wrap(rzi - qCol(3,j), 3)
516   #else          
517 <        
517 >           ljAtype_j   => identPtrList(j)%this
518             rxij = wrap(rxi - q(1,j), 1)
519             ryij = wrap(ryi - q(2,j), 2)
520             rzij = wrap(rzi - q(3,j), 3)
# Line 399 | Line 522 | contains
522   #endif          
523             rijsq = rxij*rxij + ryij*ryij + rzij*rzij
524  
525 < #ifdef MPI
526 <             if (rijsq <=  rlstsq .AND. &
525 > #ifdef IS_MPI
526 >             if (rijsq <=  rlistsq .AND. &
527                    tag_j /= tag_i) then
528   #else
529 <             if (rijsq <  rlstsq) then
529 >          
530 >             if (rijsq <  rlistsq) then
531   #endif
532              
533                nlist = nlist + 1
534                if (nlist > size(list)) then
535 <                 call info("FORCE_LJ","error size list smaller then nlist")
536 <                 write(msg,*) "nlist size(list)", nlist, size(list)
413 <                 call info("FORCE_LJ",msg)
414 < #ifdef MPI
415 <                 call mpi_abort(MPI_COMM_WORLD,mpi_err)
416 < #endif
417 <                 stop
535 > !!  "Change how nlist size is done"
536 >                 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
537                endif
538                list(nlist) = j
539  
540 <              
540 >    
541                if (rijsq <  rcutsq) then
542                  
543                   r = dsqrt(rijsq)
544        
545 <                 call LJ_mix(r,pot,dudr,d2,i,j)
545 >                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
546        
547 < #ifdef MPI
548 <                e_row(i) = e_row(i) + pot*0.5
549 <                e_col(i) = e_col(i) + pot*0.5
547 > #ifdef IS_MPI
548 >                eRow(i) = eRow(i) + pot*0.5
549 >                eCol(i) = eCol(i) + pot*0.5
550   #else
551 <                pe = pe + pot
551 >                    pe = pe + pot
552   #endif                
553              
554                   efr(1,j) = -rxij
# Line 443 | Line 562 | contains
562                      ftmp = dudr * drdx1
563  
564  
565 < #ifdef MPI
566 <                    f_col(dim,j) = f_col(dim,j) - ftmp
567 <                    f_row(dim,i) = f_row(dim,i) + ftmp
565 > #ifdef IS_MPI
566 >                    fCol(dim,j) = fCol(dim,j) - ftmp
567 >                    fRow(dim,i) = fRow(dim,i) + ftmp
568   #else                    
569              
570                      f(dim,j) = f(dim,j) - ftmp
# Line 458 | Line 577 | contains
577          enddo inner
578       enddo
579  
580 < #ifdef MPI
580 > #ifdef IS_MPI
581       point(nrow + 1) = nlist + 1
582   #else
583       point(natoms) = nlist + 1
# Line 472 | Line 591 | contains
591          JEND = POINT(i+1) - 1
592          ! check thiat molecule i has neighbors
593          if (jbeg .le. jend) then
594 < #ifdef MPI
595 <           rxi = q_row(1,i)
596 <           ryi = q_row(2,i)
597 <           rzi = q_row(3,i)
594 > #ifdef IS_MPI
595 >           ljAtype_i => identPtrListRow(i)%this
596 >           rxi = qRow(1,i)
597 >           ryi = qRow(2,i)
598 >           rzi = qRow(3,i)
599   #else
600 +           ljAtype_i   => identPtrList(i)%this
601             rxi = q(1,i)
602             ryi = q(2,i)
603             rzi = q(3,i)
604   #endif
605             do jnab = jbeg, jend
606                j = list(jnab)
607 < #ifdef MPI
608 <                rxij = wrap(rxi - q_col(1,j), 1)
609 <                ryij = wrap(ryi - q_col(2,j), 2)
610 <                rzij = wrap(rzi - q_col(3,j), 3)
607 > #ifdef IS_MPI
608 >              ljAtype_j = identPtrListColumn(j)%this
609 >              rxij = wrap(rxi - qCol(1,j), 1)
610 >              ryij = wrap(ryi - qCol(2,j), 2)
611 >              rzij = wrap(rzi - qCol(3,j), 3)
612   #else
613 <                rxij = wrap(rxi - q(1,j), 1)
614 <                ryij = wrap(ryi - q(2,j), 2)
615 <                rzij = wrap(rzi - q(3,j), 3)
613 >              ljAtype_j = identPtrList(j)%this
614 >              rxij = wrap(rxi - q(1,j), 1)
615 >              ryij = wrap(ryi - q(2,j), 2)
616 >              rzij = wrap(rzi - q(3,j), 3)
617   #endif
618                rijsq = rxij*rxij + ryij*ryij + rzij*rzij
619                
# Line 498 | Line 621 | contains
621  
622                   r = dsqrt(rijsq)
623                  
624 <                 call LJ_mix(r,pot,dudr,d2,i,j)
625 < #ifdef MPI
626 <                e_row(i) = e_row(i) + pot*0.5
627 <                e_col(i) = e_col(i) + pot*0.5
624 >                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
625 > #ifdef IS_MPI
626 >                eRow(i) = eRow(i) + pot*0.5
627 >                eCol(i) = eCol(i) + pot*0.5
628   #else
629 <               if (do_pot)  pe = pe + pot
629 >                pe = pe + pot
630   #endif                
631  
632                  
# Line 515 | Line 638 | contains
638                      
639                      drdx1 = efr(dim,j) / r
640                      ftmp = dudr * drdx1
641 < #ifdef MPI
642 <                    f_col(dim,j) = f_col(dim,j) - ftmp
643 <                    f_row(dim,i) = f_row(dim,i) + ftmp
641 > #ifdef IS_MPI
642 >                    fCol(dim,j) = fCol(dim,j) - ftmp
643 >                    fRow(dim,i) = fRow(dim,i) + ftmp
644   #else                    
645                      f(dim,j) = f(dim,j) - ftmp
646                      f(dim,i) = f(dim,i) + ftmp
# Line 531 | Line 654 | contains
654  
655  
656  
657 < #ifdef MPI
657 > #ifdef IS_MPI
658      !!distribute forces
659 <    call scatter(f_row,f,plan_row3)
659 >  write(*,*) "At first scatter"
660 >    call scatter(fRow,f,plan_row3d)
661  
662 <    call scatter(f_col,f_tmp,plan_col3)
662 >    call scatter(fCol,fMPITemp,plan_col3d)
663 >
664      do i = 1,nlocal
665 <       do dim = 1,3
541 <          f(dim,i) = f(dim,i) + f_tmp(dim,i)
542 <       end do
665 >       f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
666      end do
667  
668 <
668 >    write(*,*) "Completed scatter"
669      
670      if (do_pot) then
671   ! scatter/gather pot_row into the members of my column
672 <       call scatter(e_row,e_tmp,plan_row)
672 >       call scatter(eRow,eTemp,plan_row)
673        
674         ! scatter/gather pot_local into all other procs
675         ! add resultant to get total pot
676         do i = 1, nlocal
677 <          pot_local = pot_local + e_tmp(i)
677 >          pe_local = pe_local + eTemp(i)
678         enddo
679         if (newtons_thrd) then
680 <          e_tmp = 0.0E0_DP
681 <          call scatter(e_col,e_tmp,plan_col)
680 >          eTemp = 0.0E0_DP
681 >          call scatter(eCol,eTemp,plan_col)
682            do i = 1, nlocal
683 <             pot_local = pot_local + e_tmp(i)
683 >             pe_local = pe_local + eTemp(i)
684            enddo
685         endif
686      endif
687 +    potE = pe_local
688   #endif
689  
690 +    potE = pe
691  
692 +   write(*,*) "Successfully completed force loop"
693  
694  
695    end subroutine do_lj_ff
696  
697 < !! Calculates the potential between two lj particles, optionally returns second
697 > !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
698   !! derivatives.
699    subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
700   ! arguments
# Line 581 | Line 707 | contains
707   !! Second Derivative, optional, used mainly for normal mode calculations.
708      real( kind = dp ), intent(out), optional :: d2
709      
710 <    type (lj_atype), intent(in) :: atype1
711 <    type (lj_atype), intent(in) :: atype2
710 >    type (lj_atype), pointer :: atype1
711 >    type (lj_atype), pointer :: atype2
712  
713      integer, intent(out), optional :: status
714  
# Line 590 | Line 716 | contains
716      real( kind = dp ) :: sigma
717      real( kind = dp ) :: sigma2
718      real( kind = dp ) :: sigma6
719 <    real( kind = dp ) :: epslon
719 >    real( kind = dp ) :: epsilon
720  
721      real( kind = dp ) :: rcut
722      real( kind = dp ) :: rcut2
# Line 615 | Line 741 | contains
741      if (present(status)) status = 0
742  
743   ! Look up the correct parameters in the mixing matrix
744 <    sigma   = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
745 <    sigma2  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
746 <    sigma6  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
747 <    epslon  = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
744 >    sigma    = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
745 >    sigma2   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
746 >    sigma6   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
747 >    epsilon  = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
748  
749  
750 <
750 >    
751 >
752      call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
753      
754      r2 = r * r
# Line 638 | Line 765 | contains
765      delta = -4.0E0_DP*epsilon * (tp12 - tp6)
766                                                                                
767      if (r.le.rcut) then
768 <       u = 4.0E0_DP * epsilon * (t12 - t6) + delta
768 >       pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
769         dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
770         if(doSec)  d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
771      else
772 <       u = 0.0E0_DP
772 >       pot = 0.0E0_DP
773         dudr = 0.0E0_DP
774         if(doSec) d2 = 0.0E0_DP
775      endif
# Line 654 | Line 781 | contains
781    end subroutine getLjPot
782  
783  
784 < !! Calculates the mixing for sigma or epslon based on character string
784 > !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
785    function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
786      character(len=*) :: thisParam
787      real(kind = dp)  :: param1
# Line 671 | Line 798 | contains
798  
799      case ("sigma")
800         myMixParam = 0.5_dp * (param1 + param2)
801 <    case ("epslon")
801 >    case ("epsilon")
802         myMixParam = sqrt(param1 * param2)
803      case default
804         status = -1

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines