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 240 by chuckv, Wed Jan 22 21:45:20 2003 UTC vs.
Revision 252 by chuckv, Tue Jan 28 22:16:55 2003 UTC

# Line 2 | Line 2
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.9 2003-01-22 21:45:20 chuckv Exp $, $Date: 2003-01-22 21:45:20 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
5 > !! @version $Id: lj_FF.F90,v 1.12 2003-01-28 22:16:55 chuckv Exp $, $Date: 2003-01-28 22:16:55 $, $Name: not supported by cvs2svn $, $Revision: 1.12 $
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 18 | 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  
24 !! Basic atom type for a Lennard-Jones Atom.
25  type, public :: lj_atype
26     private
27     sequence
28 !! Unique number for place in linked list
29     integer :: atype_number = 0
30 !! Unique indentifier number (ie atomic no, etc)
31     integer :: atype_ident = 0
32 !! Mass of Particle
33     real ( kind = dp )  :: mass = 0.0_dp
34 !! Lennard-Jones epslon
35     real ( kind = dp )  :: epslon = 0.0_dp
36 !! Lennard-Jones Sigma
37     real ( kind = dp )  :: sigma = 0.0_dp
38 !! Lennard-Jones Sigma Squared
39     real ( kind = dp )  :: sigma2 = 0.0_dp
40 !! Lennard-Jones Sigma to sixth
41     real ( kind = dp )  :: sigma6 = 0.0_dp
42 !! Pointer for linked list creation
43     type (lj_atype), pointer :: next => null()
44  end type lj_atype
26  
46 !! Pointer type for atype ident array
47  type, public :: lj_atypePtr
48     type (lj_atype), pointer :: this => null()
49  end type lj_atypePtr
50
51 !! Global list of lj atypes in simulation
52  type (lj_atype), pointer :: lj_atype_list => null()
27   !! LJ mixing array  
28 <  type (lj_atype), dimension(:,:), allocatable, pointer :: ljMixed =>null()
55 < !! identity pointer list for force loop.
56 <  type (lj_atypePtr), dimension(:), allocatable :: identPtrList
28 >  type (lj_atype), dimension(:,:), pointer :: ljMixed => null()
29  
30  
31   !! Neighbor list and commom arrays
# Line 64 | Line 36 | module lj_ff
36    integer :: nListAllocs = 0
37    integer, parameter :: maxListAllocs = 5
38  
67 #ifdef IS_MPI
68 ! Universal routines: All types of force calculations will need these arrays
69 ! Arrays specific to a type of force calculation should be declared in that module.
70  real( kind = dp ), allocatable, dimension(:,:) :: qRow
71  real( kind = dp ), allocatable, dimension(:,:) :: qColumn
39  
40 <  real( kind = dp ), allocatable, dimension(:,:) :: fRow
41 <  real( kind = dp ), allocatable, dimension(:,:) :: fColumn
42 <
43 <  type (lj_atypePtr), dimension(:), allocatable :: identPtrListRow
44 <  type (lj_atypePtr), dimension(:), allocatable :: identPtrListColumn
40 > !! Atype identity pointer lists
41 > #ifdef IS_MPI
42 > !! Row lj_atype pointer list
43 >  type (lj_atypePtr), dimension(:), pointer :: identPtrListRow => null()
44 > !! Column lj_atype pointer list
45 >  type (lj_atypePtr), dimension(:), pointer :: identPtrListColumn => null()
46 > #else
47 >  type( lj_identPtrList ), dimension(:), pointer :: identPtrList => null()
48   #endif
49  
50  
51 + !! Logical has lj force field module been initialized?
52 +  logical, save :: isljFFinit = .false.
53  
82  logical :: isljFFinit = .false.
54  
84
55   !! Public methods and data
56    public :: new_lj_atype
57    public :: do_lj_ff
58    public :: getLjPot
59 <  
59 >  public :: init_ljFF
60  
61    
62  
63  
64   contains
65  
66 <  subroutine new_lj_atype(ident,mass,epslon,sigma,status)
66 > !! Adds a new lj_atype to the list.
67 >  subroutine new_lj_atype(ident,mass,epsilon,sigma,status)
68      real( kind = dp ), intent(in) :: mass
69 <    real( kind = dp ), intent(in) :: epslon
69 >    real( kind = dp ), intent(in) :: epsilon
70      real( kind = dp ), intent(in) :: sigma
71      integer, intent(in) :: ident
72      integer, intent(out) :: status
73  
74 <    type (lj_atype), pointer :: this_lj_atype
104 <    type (lj_atype), pointer :: lj_atype_ptr
105 <
106 <    type (lj_atype), allocatable, dimension(:,:), pointer :: thisMix
107 <    type (lj_atype), allocatable, dimension(:,:), pointer :: oldMix
74 >    type (lj_atype), pointer :: newLJ_atype
75      integer :: alloc_error
76      integer :: atype_counter = 0
77      integer :: alloc_size
78 <
78 >    integer :: err_stat
79      status = 0
80  
81  
82  
83   ! allocate a new atype    
84 <    allocate(this_lj_atype,stat=alloc_error)
84 >    allocate(newLJ_atype,stat=alloc_error)
85      if (alloc_error /= 0 ) then
86         status = -1
87         return
88      end if
89  
90   ! assign our new lj_atype information
91 <    this_lj_atype%mass       = mass
92 <    this_lj_atype%epslon     = epslon
93 <    this_lj_atype%sigma      = sigma
94 <    this_lj_atype%sigma2     = sigma * sigma
95 <    this_lj_atype%sigma6     = this_lj_atype%sigma2 * this_lj_atype%sigma2 &
96 <         * this_lj_atype%sigma2
91 >    newLJ_atype%mass        = mass
92 >    newLJ_atype%epsilon     = epsilon
93 >    newLJ_atype%sigma       = sigma
94 >    newLJ_atype%sigma2      = sigma * sigma
95 >    newLJ_atype%sigma6      = newLJ_atype%sigma2 * newLJ_atype%sigma2 &
96 >         * newLJ_atype%sigma2
97   ! assume that this atype will be successfully added
98 <    this_lj_atype%atype_ident = ident
99 <    this_lj_atype%number = n_lj_atypes + 1
98 >    newLJ_atype%atype_ident = ident
99 >    newLJ_atype%atype_number = n_lj_atypes + 1
100  
101 <
102 < ! First time through allocate a array of size ljMixed_blocksize
103 <    if(.not. associated(ljMixed)) then
104 <       allocate(thisMix(ljMixed_blocksize,ljMixed_blocksize))
138 <       if (alloc_error /= 0 ) then
139 <          status = -1
140 <          return
141 <       end if
142 <       ljMixed => thisMix
143 < ! If we have outgrown ljMixed_blocksize, allocate a new matrix twice the size and
144 < ! point ljMix at the new matrix.
145 <    else if( (n_lj_atypes + 1) > size(ljMixed)) then
146 <       alloc_size = 2*size(ljMix)
147 <       allocate(thisMix(alloc_size,alloc_size))
148 <       if (alloc_error /= 0 ) then
149 <          status = -1
150 <          return
151 <       end if
152 < ! point oldMix at old ljMixed array
153 <       oldMix => ljMixed
154 < ! Copy oldMix into new Mixed array      
155 <       thisMix = oldMix
156 < ! Point ljMixed at new array
157 <       ljMixed => thisMix
158 < ! Free old array so we don't have a memory leak
159 <       deallocate(oldMix)
101 >    call add_atype(newLJ_atype,ljListHead,ljListTail,err_stat)
102 >    if (err_stat /= 0 ) then
103 >       status = -1
104 >       return
105      endif
161
162
163
164
165
166 ! Find bottom of atype master list
167 ! if lj_atype_list is null then we are at the top of the list.
168    if (.not. associated(lj_atype_list)) then
169       lj_atype_ptr => this_lj_atype
170       atype_counter = 1
106  
172    else ! we need to find the bottom of the list to insert new atype
173       lj_atype_ptr => lj_atype_list%next
174       atype_counter = 1
175       find_end: do
176          if (.not. associated(lj_atype_ptr%next)) then
177             exit find_end
178          end if
179 ! Set up mixing for new atype and current atype in list
180       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma  =  &
181            calcLJMix("sigma",this_lj_atype%sigma, &
182            lj_atype_prt%sigma)
183
184       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2  = &
185            ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma &
186            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma
187
188       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma6 = &
189            ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
190            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
191            * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2
192
193       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%epslon = &
194            calcLJMix("epslon",this_lj_atype%epslon, &
195            lj_atype_prt%epslon)
196
197 ! Advance to next pointer
198       lj_atype_ptr => lj_atype_ptr%next
199       atype_counter = atype_counter + 1
200          
201       end do find_end
202    end if
203
204
205
206    
207 ! Insert new atype at end of list
208    lj_atype_ptr => this_lj_atype
209 ! Increment number of atypes
210
107      n_lj_atypes = n_lj_atypes + 1
108  
213 ! Set up self mixing
109  
215    ljMix(n_lj_atypes,n_lj_atypes)%sigma  = this_lj_atype%sigma
216
217    ljMix(n_lj_atypes,n_lj_atypes)%sigma2  = ljMix(n_lj_atypes,n_lj_atypes)%sigma &
218            * ljMix(n_lj_atypes,n_lj_atypes)%sigma
219
220    ljMix(n_lj_atypes,n_lj_atypes)%sigma6 = ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
221            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
222            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2
223
224    ljMix(n_lj_atypes,n_lj_atypes)%epslon = this_lj_atype%epslon
225
226
110    end subroutine new_lj_atype
111  
112  
# Line 236 | Line 119 | contains
119   !!  Result status, success = 0, error = -1
120      integer, intent(out) :: Status
121  
122 +    integer :: alloc_stat
123 +
124      integer :: thisStat
125 +    integer :: i
126   #ifdef IS_MPI
127      integer, allocatable, dimension(:) :: identRow
128      integer, allocatable, dimension(:) :: identCol
# Line 245 | Line 131 | contains
131      integer :: alloc_stat
132   #endif
133      status = 0
248
134   !! if were're not in MPI, we just update ljatypePtrList
135   #ifndef IS_MPI
136 <    call new_ljatypePtrList(nComponents,ident,identPtrList,thisStat)
136 >    call create_IdentPtrlst(ident,ljListHead,identPtrList,thisStat)
137      if ( thisStat /= 0 ) then
138         status = -1
139         return
140      endif
141 +
142   !! Allocate pointer lists
143      allocate(point(nComponents),stat=alloc_stat)
144      if (alloc_stat /=0) then
# Line 292 | Line 178 | contains
178      call gather(ident,identCol,plan_col)
179  
180   !! Create row and col pointer lists
181 <    call new_ljatypePtrList(nrow,identRow,identPtrListRow,thisStat)
181 >    call create_IdentPtrlst(identRow,ljListTail,identPtrListRow,thisStat)
182      if (thisStat /= 0 ) then
183         status = -1
184         return
185      endif
186  
187 <    call new_ljatypePtrList(ncol,identCol,identPtrListCol,thisStat)
187 >    call create_IdentPtrlst(identCol,ljListTail,identPtrListCol,thisStat)
188      if (thisStat /= 0 ) then
189         status = -1
190         return
# Line 308 | Line 194 | contains
194      deallocate(identCol)
195      deallocate(identRow)
196  
311 !! Allocate Simulation arrays
312 !! NOTE: This bit of code should be fixed, it can cause large
313 !! memory fragmentation if call repeatedly
197  
315    if (.not.allocated(qRow)) then
316       allocate(qRow(3,nrow),stat=alloc_stat)
317       if (alloc_stat /= 0 ) then
318          status = -1
319          return
320       endif
321    else
322       deallocate(qrow)
323       allocate(qRow(3,nrow),stat=alloc_stat)
324       if (alloc_stat /= 0 ) then
325          status = -1
326          return
327       endif
328    endif
329
330    if (.not.allocated(3,qCol)) then
331       allocate(qCol(ncol),stat=alloc_stat)
332       if (alloc_stat /= 0 ) then
333          status = -1
334          return
335       endif
336    else
337       deallocate(qCol)
338       allocate(qCol(3,ncol),stat=alloc_stat)
339       if (alloc_stat /= 0 ) then
340          status = -1
341          return
342       endif
343    endif
344
345    if (.not.allocated(fRow)) then
346       allocate(fRow(3,nrow),stat=alloc_stat)
347       if (alloc_stat /= 0 ) then
348          status = -1
349          return
350       endif
351    else
352       deallocate(fRow)
353       allocate(fRow(3,nrow),stat=alloc_stat)
354       if (alloc_stat /= 0 ) then
355          status = -1
356          return
357       endif
358    endif
359
360    if (.not.allocated(fCol)) then
361       allocate(fCol(3,ncol),stat=alloc_stat)
362       if (alloc_stat /= 0 ) then
363          status = -1
364          return
365       endif
366    else
367       deallocate(fCol)
368       allocate(fCol(3,ncol),stat=alloc_stat)
369       if (alloc_stat /= 0 ) then
370          status = -1
371          return
372       endif
373    endif
198   !! Allocate neighbor lists for mpi simulations.
199      if (.not. allocated(point)) then
200         allocate(point(nrow),stat=alloc_stat)
# Line 402 | Line 226 | contains
226  
227   #endif
228      
229 <
229 >    call createMixingList(thisStat)
230 >    if (thisStat /= 0) then
231 >       status = -1
232 >       return
233 >    endif
234      isljFFinit = .true.
235  
408
236    end subroutine init_ljFF
237  
238  
239  
240  
241  
415 !! Takes an ident array and creates an atype pointer list
416 !! based on those identities
417  subroutine new_ljatypePtrList(mysize,ident,PtrList,status)
418    integer, intent(in) :: mysize
419    integer, intent(in) :: ident
420    integer, optional :: status
421    type(lj_atypePtr), dimension(:) :: PtrList
242  
243 <    integer :: thisIdent
243 >  subroutine createMixingList(status)
244 >    integer :: listSize
245 >    integer :: status
246      integer :: i
247 <    integer :: alloc_error
426 <    type (lj_atype), pointer :: tmpPtr
247 >    integer :: j
248  
249 <    if (present(status)) status = 0
249 >    integer :: outerCounter = 0
250 >    integer :: innerCounter = 0
251 >    type (lj_atype), pointer :: tmpPtrOuter => null()
252 >    type (lj_atype), pointer :: tmpPtrInner => null()
253 >    status = 0
254  
255 < ! First time through, allocate list
256 <    if (.not.(allocated)) then
257 <       allocate(PtrList(mysize))
255 >    listSize = getListLen(ljListHead)
256 >    if (listSize == 0) then
257 >       status = -1
258 >       return
259 >    end if
260 >  
261 >
262 >    if (.not. associated(ljMixed)) then
263 >       allocate(ljMixed(listSize,listSize))
264      else
265 < ! We want to creat a new ident list so free old list
266 <       deallocate(PrtList)
267 <       allocate(PtrList(mysize))
437 <    endif
265 >       status = -1
266 >       return
267 >    end if
268  
269 < ! Match pointer list
270 <    do i = 1, mysize
271 <       thisIdent = ident(i)
272 <       call getLJatype(thisIdent,tmpPtr)
273 <
274 <      if (.not. associated(tmpPtr)) then
275 <          status = -1
276 <          return
269 >    
270 >
271 >    tmpPtrOuter => ljListHead
272 >    tmpPtrInner => tmpPtrOuter%next
273 >    do while (associated(tmpPtrOuter))
274 >       outerCounter = outerCounter + 1
275 > ! do self mixing rule
276 >       ljMixed(outerCounter,outerCounter)%sigma  = tmpPtrOuter%sigma
277 >                                                                                                  
278 >       ljMixed(outerCounter,outerCounter)%sigma2  = ljMixed(outerCounter,outerCounter)%sigma &
279 >            * ljMixed(outerCounter,outerCounter)%sigma
280 >                                                                                                  
281 >       ljMixed(outerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,outerCounter)%sigma2 &
282 >            * ljMixed(outerCounter,outerCounter)%sigma2 &
283 >            * ljMixed(outerCounter,outerCounter)%sigma2
284 >                                                                                                  
285 >       ljMixed(outerCounter,outerCounter)%epsilon = tmpPtrOuter%epsilon
286 >
287 >       innerCounter = outerCounter + 1
288 >       do while (associated(tmpPtrInner))
289 >          
290 >          ljMixed(outerCounter,innerCounter)%sigma  =  &
291 >               calcLJMix("sigma",tmpPtrOuter%sigma, &
292 >               tmpPtrInner%sigma)
293 >          
294 >          ljMixed(outerCounter,innerCounter)%sigma2  = &
295 >               ljMixed(outerCounter,innerCounter)%sigma &
296 >               * ljMixed(outerCounter,innerCounter)%sigma
297 >          
298 >          ljMixed(outerCounter,innerCounter)%sigma6 = &
299 >               ljMixed(outerCounter,innerCounter)%sigma2 &
300 >               * ljMixed(outerCounter,innerCounter)%sigma2 &
301 >               * ljMixed(outerCounter,innerCounter)%sigma2
302 >          
303 >          ljMixed(outerCounter,innerCounter)%epsilon = &
304 >               calcLJMix("epsilon",tmpPtrOuter%epsilon, &
305 >               tmpPtrInner%epsilon)
306 >          ljMixed(innerCounter,outerCounter)%sigma = ljMixed(outerCounter,innerCounter)%sigma
307 >          ljMixed(innerCounter,outerCounter)%sigma2 = ljMixed(outerCounter,innerCounter)%sigma2
308 >          ljMixed(innerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,innerCounter)%sigma6
309 >          ljMixed(innerCounter,outerCounter)%epsilon = ljMixed(outerCounter,innerCounter)%epsilon
310 >
311 >
312 >          tmpPtrInner => tmpPtrInner%next
313 >          innerCounter = innerCounter + 1
314 >       end do
315 > ! advance pointers
316 >       tmpPtrOuter => tmpPtrOuter%next
317 >       if (associated(tmpPtrOuter)) then
318 >          tmpPtrInner => tmpPtrOuter%next
319         endif
320        
449       PtrList(i)%this => tmpPtr
321      end do
322  
323 <  end subroutine new_ljatypePtrList
323 >  end subroutine createMixingList
324  
454 !! Finds a lj_atype based upon numerical ident
455 !! returns a null pointer if error
456  subroutine getLJatype(ident,ljAtypePtr)
457    integer, intent(in) :: ident
458    type (lj_atype), intent(out),pointer :: ljAtypePtr => null()
459    
460    type (lj_atype), pointer :: tmplj_atype_ptr => null()
325  
462    if(.not. associated(lj_atype_list)) return
326  
464 ! Point at head of list.
465    tmplj_atype_ptr => lj_atype_list
466    find_ident: do
467       if (.not.associated(tmplj_atype_ptr)) then
468          exit find_ident
469       else if( lj_atype_ptr%atype_ident == ident)
470          ljAtypePtr => tmplj_atype_ptr
471          exit find_ident
472       endif
473       tmplj_atype_ptr => tmplj_atype_ptr%next
474    end do find_ident
327  
476  end subroutine getLJatype
328  
329  
330 +
331 +
332   !! FORCE routine Calculates Lennard Jones forces.
333   !------------------------------------------------------------->
334    subroutine do_lj_ff(q,f,potE,do_pot)
335 <    real ( kind = dp ), dimension(ndim,) :: q
336 <    real ( kind = dp ), dimension(ndim,nLRparticles) :: f
335 > !! Position array provided by C, dimensioned by getNlocal
336 >    real ( kind = dp ), dimension(3,getNlocal()) :: q
337 > !! Force array provided by C, dimensioned by getNlocal
338 >    real ( kind = dp ), dimension(3,getNlocal()) :: f
339      real ( kind = dp ) :: potE
340      logical ( kind = 2) :: do_pot
341      
# Line 488 | Line 343 | contains
343      type(lj_atype), pointer :: ljAtype_j
344  
345   #ifdef MPI
346 <  real( kind = DP ), dimension(3,ncol) :: efr
346 >  real( kind = DP ), dimension(3,getNcol()) :: efr
347    real( kind = DP ) :: pot_local
348   #else
349 < !  real( kind = DP ), dimension(3,natoms) :: efr
349 >  real( kind = DP ), dimension(3,getNlocal()) :: efr
350   #endif
351    
352 + !! Local arrays needed for MPI
353 + #ifdef IS_MPI
354 +  real(kind = dp), dimension(3:getNrow()) :: qRow
355 +  real(kind = dp), dimension(3:getNcol()) :: qCol
356 +
357 +  real(kind = dp), dimension(3:getNrow()) :: fRow
358 +  real(kind = dp), dimension(3:getNcol()) :: fCol
359 +
360 +  real(kind = dp), dimension(getNrow()) :: eRow
361 +  real(kind = dp), dimension(getNcol()) :: eCol
362 +
363 +  real(kind = dp), dimension(getNlocal()) :: eTemp
364 + #endif
365 +
366 +
367 +
368    real( kind = DP )   :: pe
369 <  logical,            :: update_nlist
369 >  logical             :: update_nlist
370  
371  
372    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
# Line 504 | Line 375 | contains
375    integer :: tag_i,tag_j
376    real( kind = DP ) ::  r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
377    real( kind = DP ) ::  rxi, ryi, rzi, rxij, ryij, rzij, rijsq
378 <  real( kind = DP ) ::  rlistsq, rcutsq
378 >  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
379  
380 + ! a rig that need to be fixed.
381 + #ifdef IS_MPI
382 +  logical :: newtons_thrd = .true.
383 +  real( kind = dp ) :: pe_local
384 +  integer :: nlocal
385 + #endif
386    integer :: nrow
387    integer :: ncol
388 +  integer :: natoms
389  
390 + ! Make sure we are properly initialized.
391    if (.not. isljFFInit) then
392       write(default_error,*) "ERROR: lj_FF has not been properly initialized"
393       return
394    endif
395 + #ifdef IS_MPI
396 +    if (.not. isMPISimSet()) then
397 +     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
398 +     return
399 +  endif
400 + #endif
401  
402 + !! initialize local variables  
403 +  natoms = getNlocal()
404 +  call getRcut(rcut,rcut2=rcutsq)
405 +  call getRlist(rlist,rlistsq)
406   #ifndef IS_MPI
407    nrow = natoms - 1
408    ncol = natoms
409   #else
410    nrow = getNrow(plan_row)
411    ncol = getNcol(plan_col)
412 +  nlocal = natoms
413    j_start = 1
414   #endif
415  
416    
417 + !! See if we need to update neighbor lists
418 +  call check(q,update_nlist)
419  
528  call check(update_nlist)
529
420   !--------------WARNING...........................
421   ! Zero variables, NOTE:::: Forces are zeroed in C
422   ! Zeroing them here could delete previously computed
423   ! Forces.
424   !------------------------------------------------
425   #ifndef IS_MPI
426 <  nloops = nloops + 1
427 <  pot = 0.0E0_DP
428 <  e = 0.0E0_DP
426 > !  nloops = nloops + 1
427 >  pe = 0.0E0_DP
428 >
429   #else
430      f_row = 0.0E0_DP
431      f_col = 0.0E0_DP
432  
433 <    pot_local = 0.0E0_DP
433 >    pe_local = 0.0E0_DP
434  
435 <    e_row = 0.0E0_DP
436 <    e_col = 0.0E0_DP
437 <    e_tmp = 0.0E0_DP
435 >    eRow = 0.0E0_DP
436 >    eCol = 0.0E0_DP
437 >    eTemp = 0.0E0_DP
438   #endif
439      efr = 0.0E0_DP
440  
# Line 554 | Line 444 | contains
444      call gather(q,qCol,plan_col3)
445   #endif
446  
557 #ifndef MPI
447  
559 #endif
560
448    if (update_nlist) then
449  
450       ! save current configuration, contruct neighbor list,
451       ! and calculate forces
452 <     call save_nlist()
452 >     call save_nlist(q)
453      
454       nlist = 0
455      
# Line 610 | Line 497 | contains
497             rijsq = rxij*rxij + ryij*ryij + rzij*rzij
498  
499   #ifdef MPI
500 <             if (rijsq <=  rlstsq .AND. &
500 >             if (rijsq <=  rlistsq .AND. &
501                    tag_j /= tag_i) then
502   #else
503 <             if (rijsq <  rlstsq) then
503 >             if (rijsq <  rlistsq) then
504   #endif
505              
506                nlist = nlist + 1
507                if (nlist > size(list)) then
508 < #warning "Change how nlist size is done"
508 > !!  "Change how nlist size is done"
509                   write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
510                endif
511                list(nlist) = j
# Line 631 | Line 518 | contains
518                   call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
519        
520   #ifdef MPI
521 <                e_row(i) = e_row(i) + pot*0.5
522 <                e_col(i) = e_col(i) + pot*0.5
521 >                eRow(i) = eRow(i) + pot*0.5
522 >                eCol(i) = eCol(i) + pot*0.5
523   #else
524                  pe = pe + pot
525   #endif                
# Line 709 | Line 596 | contains
596                  
597                   call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
598   #ifdef MPI
599 <                e_row(i) = e_row(i) + pot*0.5
600 <                e_col(i) = e_col(i) + pot*0.5
599 >                eRow(i) = eRow(i) + pot*0.5
600 >                eCol(i) = eCol(i) + pot*0.5
601   #else
602 <               if (do_pot)  pe = pe + pot
602 >                pe = pe + pot
603   #endif                
604  
605                  
# Line 745 | Line 632 | contains
632      call scatter(fRow,f,plan_row3)
633  
634      call scatter(fCol,f_tmp,plan_col3)
635 +
636      do i = 1,nlocal
637 <       do dim = 1,3
750 <          f(dim,i) = f(dim,i) + f_tmp(dim,i)
751 <       end do
637 >       f(1:3,i) = f(1:3,i) + f_tmp(1:3,i)
638      end do
639  
640  
# Line 760 | Line 646 | contains
646         ! scatter/gather pot_local into all other procs
647         ! add resultant to get total pot
648         do i = 1, nlocal
649 <          pot_local = pot_local + e_tmp(i)
649 >          pe_local = pe_local + e_tmp(i)
650         enddo
651         if (newtons_thrd) then
652            e_tmp = 0.0E0_DP
653            call scatter(e_col,e_tmp,plan_col)
654            do i = 1, nlocal
655 <             pot_local = pot_local + e_tmp(i)
655 >             pe_local = pe_local + e_tmp(i)
656            enddo
657         endif
658      endif
659 +    potE = pe_local
660   #endif
661  
662 +    potE = pe
663  
664  
777
665    end subroutine do_lj_ff
666  
667   !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
# Line 790 | Line 677 | contains
677   !! Second Derivative, optional, used mainly for normal mode calculations.
678      real( kind = dp ), intent(out), optional :: d2
679      
680 <    type (lj_atype), intent(in), pointer :: atype1
681 <    type (lj_atype), intent(in), pointer :: atype2
680 >    type (lj_atype), pointer :: atype1
681 >    type (lj_atype), pointer :: atype2
682  
683      integer, intent(out), optional :: status
684  
# Line 799 | Line 686 | contains
686      real( kind = dp ) :: sigma
687      real( kind = dp ) :: sigma2
688      real( kind = dp ) :: sigma6
689 <    real( kind = dp ) :: epslon
689 >    real( kind = dp ) :: epsilon
690  
691      real( kind = dp ) :: rcut
692      real( kind = dp ) :: rcut2
# Line 824 | Line 711 | contains
711      if (present(status)) status = 0
712  
713   ! Look up the correct parameters in the mixing matrix
714 <    sigma   = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
715 <    sigma2  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
716 <    sigma6  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
717 <    epslon  = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
714 >    sigma    = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
715 >    sigma2   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
716 >    sigma6   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
717 >    epsilon  = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
718  
719  
720  
# Line 847 | Line 734 | contains
734      delta = -4.0E0_DP*epsilon * (tp12 - tp6)
735                                                                                
736      if (r.le.rcut) then
737 <       u = 4.0E0_DP * epsilon * (t12 - t6) + delta
737 >       pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
738         dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
739         if(doSec)  d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
740      else
741 <       u = 0.0E0_DP
741 >       pot = 0.0E0_DP
742         dudr = 0.0E0_DP
743         if(doSec) d2 = 0.0E0_DP
744      endif
# Line 880 | Line 767 | contains
767  
768      case ("sigma")
769         myMixParam = 0.5_dp * (param1 + param2)
770 <    case ("epslon")
770 >    case ("epsilon")
771         myMixParam = sqrt(param1 * param2)
772      case default
773         status = -1

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines