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 230 by chuckv, Thu Jan 9 19:40:38 2003 UTC vs.
Revision 281 by chuckv, Mon Feb 24 21:25:15 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.19 2003-02-24 21:25:15 chuckv Exp $, $Date: 2003-02-24 21:25:15 $, $Name: not supported by cvs2svn $, $Revision: 1.19 $
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 !! Name of atype
22     character(len = 15) :: name = "NULL"
23 !! Unique indentifier number (ie atomic no, etc)
24     integer :: atype_ident = 0
25 !! Mass of Particle
26     real ( kind = dp )  :: mass = 0.0_dp
27 !! Lennard-Jones epslon
28     real ( kind = dp )  :: epslon = 0.0_dp
29 !! Lennard-Jones Sigma
30     real ( kind = dp )  :: sigma = 0.0_dp
31 !! Lennard-Jones Sigma Squared
32     real ( kind = dp )  :: sigma2 = 0.0_dp
33 !! Lennard-Jones Sigma to sixth
34     real ( kind = dp )  :: sigma6 = 0.0_dp
35 !! Pointer for linked list creation
36     type (lj_atype), pointer :: next => null()
37  end type lj_atype
26  
39 !! Pointer type for atype ident array
40  type :: lj_atypePtr
41     type (lj_atype), pointer :: this => null()
42  end type lj_atypePtr
43
44 !! Global list of lj atypes in simulation
45  type (lj_atype), pointer :: lj_atype_list => null()
27   !! LJ mixing array  
28 <  type (lj_atype), dimension(:,:), allocatable, pointer :: ljMixed =>null()
48 < !! identity pointer list for force loop.
49 <  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
57 < ! Universal routines: All types of force calculations will need these arrays
58 < ! Arrays specific to a type of force calculation should be declared in that module.
59 <  real( kind = dp ), allocatable, dimension(:,:) :: qRow
60 <  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  
69
70
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(name,ident,mass,epslon,sigma,status)
68 <    character( len = 15 ) :: name
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
91 <    type (lj_atype), pointer :: lj_atype_ptr
92 <
93 <    type (lj_atype), allocatable, dimension(:,:), pointer :: thisMix
94 <    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%name       = name
93 <    this_lj_atype%mass       = mass
94 <    this_lj_atype%epslon     = epslon
95 <    this_lj_atype%sigma      = sigma
96 <    this_lj_atype%sigma2     = sigma * sigma
97 <    this_lj_atype%sigma6     = this_lj_atype%sigma2 * this_lj_atype%sigma2 &
117 <         * 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))
126 <       if (alloc_error /= 0 ) then
127 <          status = -1
128 <          return
129 <       end if
130 <       ljMixed => thisMix
131 < ! If we have outgrown ljMixed_blocksize, allocate a new matrix twice the size and
132 < ! point ljMix at the new matrix.
133 <    else if( (n_lj_atypes + 1) > size(ljMixed)) then
134 <       alloc_size = 2*size(ljMix)
135 <       allocate(thisMix(alloc_size,alloc_size))
136 <       if (alloc_error /= 0 ) then
137 <          status = -1
138 <          return
139 <       end if
140 < ! point oldMix at old ljMixed array
141 <       oldMix => ljMixed
142 < ! Copy oldMix into new Mixed array      
143 <       thisMix = oldMix
144 < ! Point ljMixed at new array
145 <       ljMixed => thisMix
146 < ! Free old array so we don't have a memory leak
147 <       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
161 <       lj_atype_ptr => lj_atype_list%next
162 <       atype_counter = 1
163 <       find_end: do
164 <          if (.not. associated(lj_atype_ptr%next)) then
165 <             exit find_end
166 <          end if
167 < ! Set up mixing for new atype and current atype in list
168 <       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma  =  &
169 <            calcLJMix("sigma",this_lj_atype%sigma, &
170 <            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 &
174 <            * 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  
181       ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%epslon = &
182            calcLJMix("epslon",this_lj_atype%epslon, &
183            lj_atype_prt%epslon)
184
185 ! Advance to next pointer
186       lj_atype_ptr => lj_atype_ptr%next
187       atype_counter = atype_counter + 1
188          
189       end do find_end
190    end if
191
192
193
138      
195 ! Insert new atype at end of list
196    lj_atype_ptr => this_lj_atype
197 ! Increment number of atypes
139  
140 <    n_lj_atypes = n_lj_atypes + 1
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 < ! Set up self mixing
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 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma  = this_lj_atype%sigma
156 <
157 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma2  = ljMix(n_lj_atypes,n_lj_atypes)%sigma &
158 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma
159 <
160 <    ljMix(n_lj_atypes,n_lj_atypes)%sigma6 = ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
161 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
162 <            * ljMix(n_lj_atypes,n_lj_atypes)%sigma2
163 <
164 <    ljMix(n_lj_atypes,n_lj_atypes)%epslon = this_lj_atype%epslon
165 <
166 <
167 <  end subroutine new_lj_atype
168 <
169 <
170 <  subroutine init_ljFF()
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 < #ifdef IS_MPI
187 <
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 +  
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 + !! 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 + !! 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 +       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 +       allocate(list(ncol*listMultiplier),stat=alloc_stat)
237 +       if (alloc_stat /=0) then
238 +          status = -1
239 +          return
240 +       endif
241 +    endif
242 +
243   #endif
244 +    
245 +    call createMixingList(thisStat)
246 +    if (thisStat /= 0) then
247 +       status = -1
248 +       return
249 +    endif
250 +    isljFFinit = .true.
251  
252 +
253    end subroutine init_ljFF
254  
229 !! Takes an ident array and creates an atype pointer list
230 !! based on those identities
231  subroutine new_ljatypePtrList(mysize,ident,PtrList,status)
232    integer, intent(in) :: mysize
233    integer, intent(in) :: ident
234    integer, optional :: status
235    type(lj_atypePtr), dimension(:) :: PtrList
255  
256 <    integer :: thisIdent
256 >
257 >
258 >
259 >
260 >  subroutine createMixingList(status)
261 >    integer :: listSize
262 >    integer :: status
263      integer :: i
264 <    integer :: alloc_error
240 <    type (lj_atype), pointer :: tmpPtr
264 >    integer :: j
265  
266 <    if (present(status)) status = 0
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 < ! First time through, allocate list
273 <    if (.not.(allocated)) then
274 <       allocate(PtrList(mysize))
272 >    listSize = getListLen(ljListHead)
273 >    if (listSize == 0) then
274 >       status = -1
275 >       return
276 >    end if
277 >  
278 >
279 >    if (.not. associated(ljMixed)) then
280 >       allocate(ljMixed(listSize,listSize))
281      else
282 < ! We want to creat a new ident list so free old list
283 <       deallocate(PrtList)
284 <       allocate(PtrList(mysize))
251 <    endif
282 >       status = -1
283 >       return
284 >    end if
285  
286 < ! Match pointer list
287 <    do i = 1, mysize
288 <       thisIdent = ident(i)
289 <       call getLJatype(thisIdent,tmpPtr)
290 <
291 <      if (.not. associated(tmpPtr)) then
292 <          status = -1
293 <          return
286 >    
287 >
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 >       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        
263       PtrList(i)%this => tmpPtr
338      end do
339  
340 <  end subroutine new_ljatypePtrList
340 >  end subroutine createMixingList
341  
268 !! Finds a lj_atype based upon numerical ident
269 !! returns a null pointer if error
270  subroutine getLJatype(ident,ljAtypePtr)
271    integer, intent(in) :: ident
272    type (lj_atype), intent(out),pointer :: ljAtypePtr => null()
273    
274    type (lj_atype), pointer :: tmplj_atype_ptr => null()
342  
276    if(.not. associated(lj_atype_list)) return
343  
278 ! Point at head of list.
279    tmplj_atype_ptr => lj_atype_list
280    find_ident: do
281       if (.not.associated(tmplj_atype_ptr)) then
282          exit find_ident
283       else if( lj_atype_ptr%atype_ident == ident)
284          ljAtypePtr => tmplj_atype_ptr
285          exit find_ident
286       endif
287       tmplj_atype_ptr => tmplj_atype_ptr%next
288    end do find_ident
344  
290  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
351 >  subroutine do_lj_ff(q,f,potE,tau,do_pot)
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 > !! Stress Tensor
357 >    real( kind = dp), dimension(9) :: tau
358 >    real( kind = dp), dimension(9) :: tauTemp
359      real ( kind = dp ) :: potE
360 +    logical ( kind = 2) :: do_pot
361 +    
362 +    type(lj_atype), pointer :: ljAtype_i
363 +    type(lj_atype), pointer :: ljAtype_j
364  
365 < #ifdef MPI
366 <  real( kind = DP ), dimension(3,ncol) :: efr
367 <  real( kind = DP ) :: pot_local
303 < #else
304 < !  real( kind = DP ), dimension(3,natoms) :: efr
305 < #endif
365 >
366 >
367 >
368    
369 +
370 + #ifdef IS_MPI
371 +  real( kind = DP ) :: pot_local
372 +
373 + !! Local arrays needed for MPI
374 +  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
375 +  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
376 +
377 +  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
378 +  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
379 +  real(kind = dp), dimension(3,getNlocal()) :: fMPITemp = 0.0_dp
380 +
381 +  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
382 +  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
383 +
384 +  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
385 +
386 + #endif
387 +
388 +
389 +
390    real( kind = DP )   :: pe
391 <  logical,            :: update_nlist
309 <  logical             :: do_pot
391 >  logical             :: update_nlist
392  
393 +
394    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
395    integer :: nlist
396    integer :: j_start
397    integer :: tag_i,tag_j
398    real( kind = DP ) ::  r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
399 +  real( kind = dp ) :: fx,fy,fz
400 +  real( kind = DP ) ::  drdx, drdy, drdz
401    real( kind = DP ) ::  rxi, ryi, rzi, rxij, ryij, rzij, rijsq
402 +  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
403  
404 + ! a rig that need to be fixed.
405 + #ifdef IS_MPI
406 +  logical :: newtons_thrd = .true.
407 +  real( kind = dp ) :: pe_local
408 +  integer :: nlocal
409 + #endif
410    integer :: nrow
411    integer :: ncol
412 +  integer :: natoms
413 + !! should we calculate the stress tensor
414 +  logical  :: do_stress = .false.
415  
416  
417  
418 + ! Make sure we are properly initialized.
419 +  if (.not. isljFFInit) then
420 +     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
421 +     return
422 +  endif
423 + #ifdef IS_MPI
424 +    if (.not. isMPISimSet()) then
425 +     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
426 +     return
427 +  endif
428 + #endif
429 +
430 + !! initialize local variables  
431 +  natoms = getNlocal()
432 +  call getRcut(rcut,rcut2=rcutsq)
433 +  call getRlist(rlist,rlistsq)
434 + !! Find ensemble
435 +  if (isEnsemble("NPT")) do_stress = .true.
436 +
437   #ifndef IS_MPI
438    nrow = natoms - 1
439    ncol = natoms
440   #else
441 +  nrow = getNrow(plan_row)
442 +  ncol = getNcol(plan_col)
443 +  nlocal = natoms
444    j_start = 1
445   #endif
446  
447 <  call check(update_nlist)
447 >  
448 > !! See if we need to update neighbor lists
449 >  call check(q,update_nlist)
450 >  if (firstTime) then
451 >     update_nlist = .true.
452 >     firstTime = .false.
453 >  endif
454  
455 <  do_pot = .false.
456 <  if (present(pe)) do_pot = .true.
457 <
455 > !--------------WARNING...........................
456 > ! Zero variables, NOTE:::: Forces are zeroed in C
457 > ! Zeroing them here could delete previously computed
458 > ! Forces.
459 > !------------------------------------------------
460   #ifndef IS_MPI
461 <  nloops = nloops + 1
462 <  pot = 0.0E0_DP
463 <  f = 0.0E0_DP
339 <  e = 0.0E0_DP
461 > !  nloops = nloops + 1
462 >  pe = 0.0E0_DP
463 >
464   #else
465 <    f_row = 0.0E0_DP
466 <    f_col = 0.0E0_DP
465 >    fRow = 0.0E0_DP
466 >    fCol = 0.0E0_DP
467  
468 <    pot_local = 0.0E0_DP
468 >    pe_local = 0.0E0_DP
469  
470 <    e_row = 0.0E0_DP
471 <    e_col = 0.0E0_DP
472 <    e_tmp = 0.0E0_DP
470 >    eRow = 0.0E0_DP
471 >    eCol = 0.0E0_DP
472 >    eTemp = 0.0E0_DP
473   #endif
350    efr = 0.0E0_DP
474  
475   ! communicate MPI positions
476 < #ifdef MPI    
477 <    call gather(q,q_row,plan_row3)
478 <    call gather(q,q_col,plan_col3)
476 > #ifdef IS_MPI    
477 >    call gather(q,qRow,plan_row3d)
478 >    call gather(q,qCol,plan_col3d)
479   #endif
480  
358 #ifndef MPI
481  
360 #endif
361
482    if (update_nlist) then
483  
484       ! save current configuration, contruct neighbor list,
485       ! and calculate forces
486 <     call save_nlist()
486 >     call save_nlist(q)
487      
488       nlist = 0
489      
490 <    
490 >    
491  
492       do i = 1, nrow
493          point(i) = nlist + 1
494 < #ifdef MPI
495 <        tag_i = tag_row(i)
496 <        rxi = q_row(1,i)
497 <        ryi = q_row(2,i)
498 <        rzi = q_row(3,i)
494 > #ifdef IS_MPI
495 >        ljAtype_i => identPtrListRow(i)%this
496 >        tag_i = tagRow(i)
497 >        rxi = qRow(1,i)
498 >        ryi = qRow(2,i)
499 >        rzi = qRow(3,i)
500   #else
501 +        ljAtype_i   => identPtrList(i)%this
502          j_start = i + 1
503          rxi = q(1,i)
504          ryi = q(2,i)
# Line 384 | Line 506 | contains
506   #endif
507  
508          inner: do j = j_start, ncol
509 < #ifdef MPI
510 <           tag_j = tag_col(j)
509 > #ifdef IS_MPI
510 > ! Assign identity pointers and tags
511 >           ljAtype_j => identPtrListColumn(j)%this
512 >           tag_j = tagColumn(j)
513             if (newtons_thrd) then
514                if (tag_i <= tag_j) then
515                   if (mod(tag_i + tag_j,2) == 0) cycle inner
# Line 394 | Line 518 | contains
518                endif
519             endif
520  
521 <           rxij = wrap(rxi - q_col(1,j), 1)
522 <           ryij = wrap(ryi - q_col(2,j), 2)
523 <           rzij = wrap(rzi - q_col(3,j), 3)
521 >           rxij = wrap(rxi - qCol(1,j), 1)
522 >           ryij = wrap(ryi - qCol(2,j), 2)
523 >           rzij = wrap(rzi - qCol(3,j), 3)
524   #else          
525 <        
525 >           ljAtype_j   => identPtrList(j)%this
526             rxij = wrap(rxi - q(1,j), 1)
527             ryij = wrap(ryi - q(2,j), 2)
528             rzij = wrap(rzi - q(3,j), 3)
# Line 406 | Line 530 | contains
530   #endif          
531             rijsq = rxij*rxij + ryij*ryij + rzij*rzij
532  
533 < #ifdef MPI
534 <             if (rijsq <=  rlstsq .AND. &
533 > #ifdef IS_MPI
534 >             if (rijsq <=  rlistsq .AND. &
535                    tag_j /= tag_i) then
536   #else
537 <             if (rijsq <  rlstsq) then
537 >          
538 >             if (rijsq <  rlistsq) then
539   #endif
540              
541                nlist = nlist + 1
542                if (nlist > size(list)) then
543 <                 call info("FORCE_LJ","error size list smaller then nlist")
544 <                 write(msg,*) "nlist size(list)", nlist, size(list)
420 <                 call info("FORCE_LJ",msg)
421 < #ifdef MPI
422 <                 call mpi_abort(MPI_COMM_WORLD,mpi_err)
423 < #endif
424 <                 stop
543 > !!  "Change how nlist size is done"
544 >                 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
545                endif
546                list(nlist) = j
547  
548 <              
548 >    
549                if (rijsq <  rcutsq) then
550                  
551                   r = dsqrt(rijsq)
552        
553 <                 call LJ_mix(r,pot,dudr,d2,i,j)
553 >                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
554        
555 < #ifdef MPI
556 <                e_row(i) = e_row(i) + pot*0.5
557 <                e_col(i) = e_col(i) + pot*0.5
555 > #ifdef IS_MPI
556 >                eRow(i) = eRow(i) + pot*0.5
557 >                eCol(i) = eCol(i) + pot*0.5
558   #else
559 <                pe = pe + pot
559 >                    pe = pe + pot
560   #endif                
561              
562 <                 efr(1,j) = -rxij
563 <                 efr(2,j) = -ryij
564 <                 efr(3,j) = -rzij
565 <
566 <                 do dim = 1, 3  
567 <
568 <            
569 <                    drdx1 = efr(dim,j) / r
570 <                    ftmp = dudr * drdx1
571 <
572 <
573 < #ifdef MPI
574 <                    f_col(dim,j) = f_col(dim,j) - ftmp
575 <                    f_row(dim,i) = f_row(dim,i) + ftmp
576 < #else                    
577 <            
578 <                    f(dim,j) = f(dim,j) - ftmp
579 <                    f(dim,i) = f(dim,i) + ftmp
580 <
581 < #endif                    
582 <                 enddo
583 <              endif
584 <           endif
585 <        enddo inner
562 >                drdx = -rxij / r
563 >                drdy = -ryij / r
564 >                drdz = -rzij / r
565 >                
566 >                fx = dudr * drdx
567 >                fy = dudr * drdy
568 >                fz = dudr * drdz
569 >                
570 > #ifdef IS_MPI
571 >                fCol(1,j) = fCol(1,j) - fx
572 >                fCol(2,j) = fCol(2,j) - fy
573 >                fCol(3,j) = fCol(3,j) - fz
574 >                
575 >                fRow(1,j) = fRow(1,j) + fx
576 >                fRow(2,j) = fRow(2,j) + fy
577 >                fRow(3,j) = fRow(3,j) + fz
578 > #else
579 >                f(1,j) = f(1,j) - fx
580 >                f(2,j) = f(2,j) - fy
581 >                f(3,j) = f(3,j) - fz
582 >                f(1,i) = f(1,i) + fx
583 >                f(2,i) = f(2,i) + fy
584 >                f(3,i) = f(3,i) + fz
585 > #endif
586 >                
587 >                if (do_stress) then
588 >                   tauTemp(1) = tauTemp(1) + fx * rxij
589 >                   tauTemp(2) = tauTemp(2) + fx * ryij
590 >                   tauTemp(3) = tauTemp(3) + fx * rzij
591 >                   tauTemp(4) = tauTemp(4) + fy * rxij
592 >                   tauTemp(5) = tauTemp(5) + fy * ryij
593 >                   tauTemp(6) = tauTemp(6) + fy * rzij
594 >                   tauTemp(7) = tauTemp(7) + fz * rxij
595 >                   tauTemp(8) = tauTemp(8) + fz * ryij
596 >                   tauTemp(9) = tauTemp(9) + fz * rzij
597 >                endif
598 >             endif
599 >          enddo inner
600       enddo
601  
602 < #ifdef MPI
602 > #ifdef IS_MPI
603       point(nrow + 1) = nlist + 1
604   #else
605       point(natoms) = nlist + 1
# Line 479 | Line 613 | contains
613          JEND = POINT(i+1) - 1
614          ! check thiat molecule i has neighbors
615          if (jbeg .le. jend) then
616 < #ifdef MPI
617 <           rxi = q_row(1,i)
618 <           ryi = q_row(2,i)
619 <           rzi = q_row(3,i)
616 > #ifdef IS_MPI
617 >           ljAtype_i => identPtrListRow(i)%this
618 >           rxi = qRow(1,i)
619 >           ryi = qRow(2,i)
620 >           rzi = qRow(3,i)
621   #else
622 +           ljAtype_i   => identPtrList(i)%this
623             rxi = q(1,i)
624             ryi = q(2,i)
625             rzi = q(3,i)
626   #endif
627             do jnab = jbeg, jend
628                j = list(jnab)
629 < #ifdef MPI
630 <                rxij = wrap(rxi - q_col(1,j), 1)
631 <                ryij = wrap(ryi - q_col(2,j), 2)
632 <                rzij = wrap(rzi - q_col(3,j), 3)
629 > #ifdef IS_MPI
630 >              ljAtype_j = identPtrListColumn(j)%this
631 >              rxij = wrap(rxi - qCol(1,j), 1)
632 >              ryij = wrap(ryi - qCol(2,j), 2)
633 >              rzij = wrap(rzi - qCol(3,j), 3)
634   #else
635 <                rxij = wrap(rxi - q(1,j), 1)
636 <                ryij = wrap(ryi - q(2,j), 2)
637 <                rzij = wrap(rzi - q(3,j), 3)
635 >              ljAtype_j = identPtrList(j)%this
636 >              rxij = wrap(rxi - q(1,j), 1)
637 >              ryij = wrap(ryi - q(2,j), 2)
638 >              rzij = wrap(rzi - q(3,j), 3)
639   #endif
640                rijsq = rxij*rxij + ryij*ryij + rzij*rzij
641                
# Line 505 | Line 643 | contains
643  
644                   r = dsqrt(rijsq)
645                  
646 <                 call LJ_mix(r,pot,dudr,d2,i,j)
647 < #ifdef MPI
648 <                e_row(i) = e_row(i) + pot*0.5
649 <                e_col(i) = e_col(i) + pot*0.5
646 >                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
647 > #ifdef IS_MPI
648 >                eRow(i) = eRow(i) + pot*0.5
649 >                eCol(i) = eCol(i) + pot*0.5
650   #else
651 <               if (do_pot)  pe = pe + pot
651 >                pe = pe + pot
652   #endif                
653 +  
654 +                drdx = -rxij / r
655 +                drdy = -ryij / r
656 +                drdz = -rzij / r
657 +                
658 +                fx = dudr * drdx
659 +                fy = dudr * drdy
660 +                fz = dudr * drdz
661 +                
662 + #ifdef IS_MPI
663 +                fCol(1,j) = fCol(1,j) - fx
664 +                fCol(2,j) = fCol(2,j) - fy
665 +                fCol(3,j) = fCol(3,j) - fz
666 +                
667 +                fRow(1,j) = fRow(1,j) + fx
668 +                fRow(2,j) = fRow(2,j) + fy
669 +                fRow(3,j) = fRow(3,j) + fz
670 + #else
671 +                f(1,j) = f(1,j) - fx
672 +                f(2,j) = f(2,j) - fy
673 +                f(3,j) = f(3,j) - fz
674 +                f(1,i) = f(1,i) + fx
675 +                f(2,i) = f(2,i) + fy
676 +                f(3,i) = f(3,i) + fz
677 + #endif
678 +                
679 +                if (do_stress) then
680 +                   tauTemp(1) = tauTemp(1) + fx * rxij
681 +                   tauTemp(2) = tauTemp(2) + fx * ryij
682 +                   tauTemp(3) = tauTemp(3) + fx * rzij
683 +                   tauTemp(4) = tauTemp(4) + fy * rxij
684 +                   tauTemp(5) = tauTemp(5) + fy * ryij
685 +                   tauTemp(6) = tauTemp(6) + fy * rzij
686 +                   tauTemp(7) = tauTemp(7) + fz * rxij
687 +                   tauTemp(8) = tauTemp(8) + fz * ryij
688 +                   tauTemp(9) = tauTemp(9) + fz * rzij
689 +                endif
690 +                
691 +                
692 +             endif
693 +          enddo
694 +       endif
695 +    enddo
696 + endif
697 +
698  
516                
517                 efr(1,j) = -rxij
518                 efr(2,j) = -ryij
519                 efr(3,j) = -rzij
699  
700 <                 do dim = 1, 3                        
701 <                    
523 <                    drdx1 = efr(dim,j) / r
524 <                    ftmp = dudr * drdx1
525 < #ifdef MPI
526 <                    f_col(dim,j) = f_col(dim,j) - ftmp
527 <                    f_row(dim,i) = f_row(dim,i) + ftmp
528 < #else                    
529 <                    f(dim,j) = f(dim,j) - ftmp
530 <                    f(dim,i) = f(dim,i) + ftmp
531 < #endif                    
532 <                 enddo
533 <              endif
534 <           enddo
535 <        endif
536 <     enddo
537 <  endif
700 > #ifdef IS_MPI
701 >    !!distribute forces
702  
703 +    call scatter(fRow,f,plan_row3d)
704  
705 +    call scatter(fCol,fMPITemp,plan_col3d)
706  
541 #ifdef MPI
542    !!distribute forces
543    call scatter(f_row,f,plan_row3)
544
545    call scatter(f_col,f_tmp,plan_col3)
707      do i = 1,nlocal
708 <       do dim = 1,3
548 <          f(dim,i) = f(dim,i) + f_tmp(dim,i)
549 <       end do
708 >       f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
709      end do
710  
711  
712      
713      if (do_pot) then
714 < ! scatter/gather pot_row into the members of my column
715 <  call scatter(e_row,e_tmp,plan_row)
714 >       ! scatter/gather pot_row into the members of my column
715 >       call scatter(eRow,eTemp,plan_row)
716        
717         ! scatter/gather pot_local into all other procs
718         ! add resultant to get total pot
719         do i = 1, nlocal
720 <          pot_local = pot_local + e_tmp(i)
720 >          pe_local = pe_local + eTemp(i)
721         enddo
722         if (newtons_thrd) then
723 <          e_tmp = 0.0E0_DP
724 <          call scatter(e_col,e_tmp,plan_col)
723 >          eTemp = 0.0E0_DP
724 >          call scatter(eCol,eTemp,plan_col)
725            do i = 1, nlocal
726 <             pot_local = pot_local + e_tmp(i)
726 >             pe_local = pe_local + eTemp(i)
727            enddo
728         endif
729 +       pe = pe_local
730      endif
731 +
732   #endif
733  
734 +    potE = pe
735  
736  
737 +    if (do_stress) then
738 + #ifdef IS_MPI
739 +       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
740 +            mpi_comm_world,mpi_err)
741 + #else
742 +       tau = tauTemp
743 + #endif      
744 +    endif
745  
746 +
747    end subroutine do_lj_ff
748  
749 < !! Calculates the potential between two lj particles, optionally returns second
749 > !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
750   !! derivatives.
751    subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
752   ! arguments
# Line 588 | Line 759 | contains
759   !! Second Derivative, optional, used mainly for normal mode calculations.
760      real( kind = dp ), intent(out), optional :: d2
761      
762 <    type (lj_atype), intent(in) :: atype1
763 <    type (lj_atype), intent(in) :: atype2
762 >    type (lj_atype), pointer :: atype1
763 >    type (lj_atype), pointer :: atype2
764  
765      integer, intent(out), optional :: status
766  
# Line 597 | Line 768 | contains
768      real( kind = dp ) :: sigma
769      real( kind = dp ) :: sigma2
770      real( kind = dp ) :: sigma6
771 <    real( kind = dp ) :: epslon
771 >    real( kind = dp ) :: epsilon
772  
773      real( kind = dp ) :: rcut
774      real( kind = dp ) :: rcut2
# Line 622 | Line 793 | contains
793      if (present(status)) status = 0
794  
795   ! Look up the correct parameters in the mixing matrix
796 <    sigma   = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
797 <    sigma2  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
798 <    sigma6  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
799 <    epslon  = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
796 >    sigma    = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
797 >    sigma2   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
798 >    sigma6   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
799 >    epsilon  = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
800  
801  
802 <
802 >    
803 >
804      call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
805      
806      r2 = r * r
# Line 645 | Line 817 | contains
817      delta = -4.0E0_DP*epsilon * (tp12 - tp6)
818                                                                                
819      if (r.le.rcut) then
820 <       u = 4.0E0_DP * epsilon * (t12 - t6) + delta
820 >       pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
821         dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
822         if(doSec)  d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
823      else
824 <       u = 0.0E0_DP
824 >       pot = 0.0E0_DP
825         dudr = 0.0E0_DP
826         if(doSec) d2 = 0.0E0_DP
827      endif
# Line 661 | Line 833 | contains
833    end subroutine getLjPot
834  
835  
836 < !! Calculates the mixing for sigma or epslon based on character string
836 > !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
837    function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
838      character(len=*) :: thisParam
839      real(kind = dp)  :: param1
840      real(kind = dp)  :: param2
841      real(kind = dp ) :: myMixParam
842 +    character(len = getStringLen()) :: thisMixingRule
843      integer, optional :: status
844  
845 <
845 > !! get the mixing rules from the simulation
846 >    thisMixingRule = returnMixingRules()
847      myMixParam = 0.0_dp
848  
849      if (present(status)) status = 0
850 <
851 <    select case (thisParam)
852 <
853 <    case ("sigma")
854 <       myMixParam = 0.5_dp * (param1 + param2)
855 <    case ("epslon")
856 <       myMixParam = sqrt(param1 * param2)
850 >    select case (thisMixingRule)
851 >       case ("standard")
852 >          select case (thisParam)
853 >          case ("sigma")
854 >             myMixParam = 0.5_dp * (param1 + param2)
855 >          case ("epsilon")
856 >             myMixParam = sqrt(param1 * param2)
857 >          case default
858 >             status = -1
859 >          end select
860 >    case("LJglass")
861      case default
862         status = -1
863      end select
686
864    end function calcLJMix
865  
866  

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines