ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
Revision: 281
Committed: Mon Feb 24 21:25:15 2003 UTC (21 years, 4 months ago) by chuckv
File size: 23542 byte(s)
Log Message:
Changes they are a comming....

File Contents

# User Rev Content
1 chuckv 239 !! 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 chuckv 281 !! @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 chuckv 239
7    
8    
9 chuckv 215 module lj_ff
10     use simulation
11 chuckv 246 use definitions
12 chuckv 247 use generic_atypes
13 chuckv 230 #ifdef IS_MPI
14     use mpiSimulation
15     #endif
16 chuckv 215 implicit none
17 chuckv 230 PRIVATE
18 chuckv 215
19 chuckv 230 !! Number of lj_atypes in lj_atype_list
20 chuckv 215 integer, save :: n_lj_atypes = 0
21    
22 chuckv 247 !! Global list of lj atypes in simulation
23     type (lj_atype), pointer :: ljListHead => null()
24     type (lj_atype), pointer :: ljListTail => null()
25 chuckv 230
26 chuckv 215
27 chuckv 230 !! LJ mixing array
28 chuckv 246 type (lj_atype), dimension(:,:), pointer :: ljMixed => null()
29 chuckv 215
30 chuckv 230
31     !! Neighbor list and commom arrays
32 chuckv 239 !! This should eventally get moved to a neighbor list type
33 chuckv 230 integer, allocatable, dimension(:) :: point
34     integer, allocatable, dimension(:) :: list
35 chuckv 239 integer, parameter :: listMultiplier = 80
36     integer :: nListAllocs = 0
37     integer, parameter :: maxListAllocs = 5
38 chuckv 230
39 chuckv 253 logical, save :: firstTime = .True.
40 chuckv 247
41     !! Atype identity pointer lists
42 chuckv 230 #ifdef IS_MPI
43 chuckv 246 !! Row lj_atype pointer list
44 chuckv 253 type (lj_identPtrList), dimension(:), pointer :: identPtrListRow => null()
45 chuckv 246 !! Column lj_atype pointer list
46 chuckv 253 type (lj_identPtrList), dimension(:), pointer :: identPtrListColumn => null()
47 chuckv 247 #else
48     type( lj_identPtrList ), dimension(:), pointer :: identPtrList => null()
49 chuckv 230 #endif
50    
51    
52 chuckv 246 !! Logical has lj force field module been initialized?
53     logical, save :: isljFFinit = .false.
54 chuckv 230
55    
56     !! Public methods and data
57 chuckv 215 public :: new_lj_atype
58 chuckv 230 public :: do_lj_ff
59     public :: getLjPot
60 chuckv 246 public :: init_ljFF
61 chuckv 215
62 chuckv 230
63    
64    
65 chuckv 215 contains
66    
67 chuckv 247 !! Adds a new lj_atype to the list.
68 chuckv 246 subroutine new_lj_atype(ident,mass,epsilon,sigma,status)
69 chuckv 215 real( kind = dp ), intent(in) :: mass
70 chuckv 246 real( kind = dp ), intent(in) :: epsilon
71 chuckv 230 real( kind = dp ), intent(in) :: sigma
72     integer, intent(in) :: ident
73 chuckv 215 integer, intent(out) :: status
74    
75 chuckv 247 type (lj_atype), pointer :: newLJ_atype
76 chuckv 216 integer :: alloc_error
77     integer :: atype_counter = 0
78 chuckv 230 integer :: alloc_size
79 chuckv 247 integer :: err_stat
80 chuckv 215 status = 0
81    
82 chuckv 230
83    
84     ! allocate a new atype
85 chuckv 247 allocate(newLJ_atype,stat=alloc_error)
86 chuckv 216 if (alloc_error /= 0 ) then
87     status = -1
88     return
89     end if
90    
91     ! assign our new lj_atype information
92 chuckv 247 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 chuckv 230 ! assume that this atype will be successfully added
99 chuckv 247 newLJ_atype%atype_ident = ident
100     newLJ_atype%atype_number = n_lj_atypes + 1
101 chuckv 216
102 chuckv 247 call add_atype(newLJ_atype,ljListHead,ljListTail,err_stat)
103     if (err_stat /= 0 ) then
104     status = -1
105     return
106 chuckv 230 endif
107    
108     n_lj_atypes = n_lj_atypes + 1
109    
110    
111 chuckv 215 end subroutine new_lj_atype
112    
113    
114 chuckv 239 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 chuckv 215
123 chuckv 246 integer :: alloc_stat
124    
125 chuckv 239 integer :: thisStat
126 chuckv 246 integer :: i
127 chuckv 260
128     integer :: myNode
129 chuckv 230 #ifdef IS_MPI
130 chuckv 239 integer, allocatable, dimension(:) :: identRow
131     integer, allocatable, dimension(:) :: identCol
132     integer :: nrow
133     integer :: ncol
134     #endif
135     status = 0
136 chuckv 254
137    
138 chuckv 258
139 chuckv 254
140 chuckv 239 !! if were're not in MPI, we just update ljatypePtrList
141     #ifndef IS_MPI
142 chuckv 247 call create_IdentPtrlst(ident,ljListHead,identPtrList,thisStat)
143 chuckv 239 if ( thisStat /= 0 ) then
144     status = -1
145     return
146     endif
147 chuckv 247
148 chuckv 239 !! 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 chuckv 230
161 chuckv 239 ! if were're in MPI, we also have to worry about row and col lists
162     #else
163 chuckv 254
164 chuckv 239 ! We can only set up forces if mpiSimulation has been setup.
165     if (.not. isMPISimSet()) then
166 chuckv 254 write(default_error,*) "MPI is not set"
167 chuckv 239 status = -1
168     return
169     endif
170 chuckv 254 nrow = getNrow(plan_row)
171     ncol = getNcol(plan_col)
172 chuckv 260 mynode = getMyNode()
173 chuckv 239 !! 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 chuckv 215
180 chuckv 239 allocate(identCol(ncol),stat=alloc_stat)
181     if (alloc_stat /= 0 ) then
182     status = -1
183     return
184     endif
185 chuckv 254
186 chuckv 239 !! Gather idents into row and column idents
187 chuckv 254
188 chuckv 239 call gather(ident,identRow,plan_row)
189     call gather(ident,identCol,plan_col)
190 chuckv 258
191 chuckv 260
192 chuckv 239 !! Create row and col pointer lists
193 chuckv 260
194 chuckv 254 call create_IdentPtrlst(identRow,ljListHead,identPtrListRow,thisStat)
195 chuckv 239 if (thisStat /= 0 ) then
196     status = -1
197     return
198     endif
199 chuckv 260
200 chuckv 254 call create_IdentPtrlst(identCol,ljListHead,identPtrListColumn,thisStat)
201 chuckv 239 if (thisStat /= 0 ) then
202     status = -1
203     return
204     endif
205 chuckv 260
206 chuckv 239 !! free temporary ident arrays
207 chuckv 258 if (allocated(identCol)) then
208     deallocate(identCol)
209     end if
210     if (allocated(identCol)) then
211     deallocate(identRow)
212     endif
213 chuckv 239
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 chuckv 230 #endif
244 chuckv 239
245 chuckv 247 call createMixingList(thisStat)
246     if (thisStat /= 0) then
247     status = -1
248     return
249     endif
250 chuckv 239 isljFFinit = .true.
251    
252 chuckv 261
253 chuckv 230 end subroutine init_ljFF
254    
255 chuckv 239
256    
257    
258    
259 chuckv 230
260 chuckv 247 subroutine createMixingList(status)
261     integer :: listSize
262     integer :: status
263 chuckv 230 integer :: i
264 chuckv 247 integer :: j
265 chuckv 230
266 chuckv 247 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 chuckv 230
272 chuckv 247 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 chuckv 230 else
282 chuckv 247 status = -1
283     return
284     end if
285 chuckv 230
286 chuckv 247
287 chuckv 252
288 chuckv 247 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 chuckv 230 endif
337    
338     end do
339    
340 chuckv 247 end subroutine createMixingList
341 chuckv 230
342    
343 chuckv 246
344 chuckv 230
345    
346 chuckv 246
347    
348    
349 chuckv 239 !! FORCE routine Calculates Lennard Jones forces.
350 chuckv 230 !------------------------------------------------------------->
351 chuckv 281 subroutine do_lj_ff(q,f,potE,tau,do_pot)
352 chuckv 246 !! 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 chuckv 281 !! Stress Tensor
357     real( kind = dp), dimension(9) :: tau
358     real( kind = dp), dimension(9) :: tauTemp
359 chuckv 222 real ( kind = dp ) :: potE
360 mmeineke 235 logical ( kind = 2) :: do_pot
361 chuckv 239
362     type(lj_atype), pointer :: ljAtype_i
363     type(lj_atype), pointer :: ljAtype_j
364    
365 chuckv 281
366    
367    
368    
369    
370 chuckv 253 #ifdef IS_MPI
371 chuckv 230 real( kind = DP ) :: pot_local
372 chuckv 281
373 chuckv 247 !! Local arrays needed for MPI
374 chuckv 281 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 chuckv 247
377 chuckv 281 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 chuckv 247
381 chuckv 281 real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
382     real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
383 chuckv 247
384 chuckv 281 real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
385 chuckv 247
386 chuckv 281 #endif
387 chuckv 247
388    
389 chuckv 281
390 chuckv 230 real( kind = DP ) :: pe
391 chuckv 246 logical :: update_nlist
392 chuckv 216
393 chuckv 232
394 chuckv 230 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 chuckv 281 real( kind = dp ) :: fx,fy,fz
400     real( kind = DP ) :: drdx, drdy, drdz
401 chuckv 230 real( kind = DP ) :: rxi, ryi, rzi, rxij, ryij, rzij, rijsq
402 chuckv 246 real( kind = DP ) :: rlistsq, rcutsq,rlist,rcut
403 chuckv 222
404 chuckv 246 ! 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 chuckv 230 integer :: nrow
411     integer :: ncol
412 chuckv 246 integer :: natoms
413 chuckv 281 !! should we calculate the stress tensor
414     logical :: do_stress = .false.
415 chuckv 222
416 chuckv 253
417    
418 chuckv 246 ! Make sure we are properly initialized.
419 chuckv 239 if (.not. isljFFInit) then
420     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
421     return
422     endif
423 chuckv 246 #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 chuckv 222
430 chuckv 246 !! initialize local variables
431     natoms = getNlocal()
432     call getRcut(rcut,rcut2=rcutsq)
433     call getRlist(rlist,rlistsq)
434 chuckv 281 !! Find ensemble
435     if (isEnsemble("NPT")) do_stress = .true.
436 chuckv 253
437 chuckv 230 #ifndef IS_MPI
438     nrow = natoms - 1
439     ncol = natoms
440     #else
441 chuckv 239 nrow = getNrow(plan_row)
442     ncol = getNcol(plan_col)
443 chuckv 246 nlocal = natoms
444 chuckv 230 j_start = 1
445     #endif
446 chuckv 222
447 chuckv 239
448 chuckv 246 !! See if we need to update neighbor lists
449     call check(q,update_nlist)
450 chuckv 253 if (firstTime) then
451     update_nlist = .true.
452     firstTime = .false.
453     endif
454 chuckv 239
455     !--------------WARNING...........................
456     ! Zero variables, NOTE:::: Forces are zeroed in C
457     ! Zeroing them here could delete previously computed
458     ! Forces.
459     !------------------------------------------------
460 chuckv 230 #ifndef IS_MPI
461 chuckv 246 ! nloops = nloops + 1
462     pe = 0.0E0_DP
463    
464 chuckv 230 #else
465 chuckv 253 fRow = 0.0E0_DP
466     fCol = 0.0E0_DP
467 chuckv 230
468 chuckv 246 pe_local = 0.0E0_DP
469 chuckv 230
470 chuckv 246 eRow = 0.0E0_DP
471     eCol = 0.0E0_DP
472     eTemp = 0.0E0_DP
473 chuckv 230 #endif
474 chuckv 261
475 chuckv 230 ! communicate MPI positions
476 chuckv 253 #ifdef IS_MPI
477     call gather(q,qRow,plan_row3d)
478     call gather(q,qCol,plan_col3d)
479 chuckv 230 #endif
480    
481 chuckv 261
482 chuckv 230 if (update_nlist) then
483    
484     ! save current configuration, contruct neighbor list,
485     ! and calculate forces
486 chuckv 246 call save_nlist(q)
487 chuckv 230
488     nlist = 0
489    
490 chuckv 253
491 chuckv 230
492     do i = 1, nrow
493     point(i) = nlist + 1
494 chuckv 253 #ifdef IS_MPI
495 chuckv 239 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 chuckv 230 #else
501 chuckv 239 ljAtype_i => identPtrList(i)%this
502 chuckv 230 j_start = i + 1
503     rxi = q(1,i)
504     ryi = q(2,i)
505     rzi = q(3,i)
506     #endif
507    
508     inner: do j = j_start, ncol
509 chuckv 253 #ifdef IS_MPI
510 chuckv 239 ! Assign identity pointers and tags
511     ljAtype_j => identPtrListColumn(j)%this
512 chuckv 254 tag_j = tagColumn(j)
513 chuckv 230 if (newtons_thrd) then
514     if (tag_i <= tag_j) then
515     if (mod(tag_i + tag_j,2) == 0) cycle inner
516     else
517     if (mod(tag_i + tag_j,2) == 1) cycle inner
518     endif
519     endif
520    
521 chuckv 239 rxij = wrap(rxi - qCol(1,j), 1)
522     ryij = wrap(ryi - qCol(2,j), 2)
523     rzij = wrap(rzi - qCol(3,j), 3)
524 chuckv 230 #else
525 chuckv 239 ljAtype_j => identPtrList(j)%this
526 chuckv 230 rxij = wrap(rxi - q(1,j), 1)
527     ryij = wrap(ryi - q(2,j), 2)
528     rzij = wrap(rzi - q(3,j), 3)
529    
530     #endif
531     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
532    
533 chuckv 253 #ifdef IS_MPI
534 chuckv 246 if (rijsq <= rlistsq .AND. &
535 chuckv 230 tag_j /= tag_i) then
536     #else
537 chuckv 253
538 chuckv 246 if (rijsq < rlistsq) then
539 chuckv 230 #endif
540    
541     nlist = nlist + 1
542     if (nlist > size(list)) then
543 chuckv 246 !! "Change how nlist size is done"
544 chuckv 239 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
545 chuckv 230 endif
546     list(nlist) = j
547    
548 chuckv 253
549 chuckv 230 if (rijsq < rcutsq) then
550    
551     r = dsqrt(rijsq)
552    
553 chuckv 239 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
554 chuckv 230
555 chuckv 253 #ifdef IS_MPI
556 chuckv 246 eRow(i) = eRow(i) + pot*0.5
557     eCol(i) = eCol(i) + pot*0.5
558 chuckv 230 #else
559 chuckv 253 pe = pe + pot
560 chuckv 230 #endif
561    
562 chuckv 281 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 chuckv 253 #ifdef IS_MPI
571 chuckv 281 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 chuckv 230 enddo
601    
602 chuckv 253 #ifdef IS_MPI
603 chuckv 230 point(nrow + 1) = nlist + 1
604     #else
605     point(natoms) = nlist + 1
606     #endif
607    
608     else
609    
610     ! use the list to find the neighbors
611     do i = 1, nrow
612     JBEG = POINT(i)
613     JEND = POINT(i+1) - 1
614     ! check thiat molecule i has neighbors
615     if (jbeg .le. jend) then
616 chuckv 253 #ifdef IS_MPI
617 chuckv 239 ljAtype_i => identPtrListRow(i)%this
618     rxi = qRow(1,i)
619     ryi = qRow(2,i)
620     rzi = qRow(3,i)
621 chuckv 230 #else
622 chuckv 239 ljAtype_i => identPtrList(i)%this
623 chuckv 230 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 chuckv 253 #ifdef IS_MPI
630 chuckv 239 ljAtype_j = identPtrListColumn(j)%this
631 chuckv 254 rxij = wrap(rxi - qCol(1,j), 1)
632     ryij = wrap(ryi - qCol(2,j), 2)
633     rzij = wrap(rzi - qCol(3,j), 3)
634 chuckv 230 #else
635 chuckv 239 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 chuckv 230 #endif
640     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
641    
642     if (rijsq < rcutsq) then
643    
644     r = dsqrt(rijsq)
645    
646 chuckv 239 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
647 chuckv 253 #ifdef IS_MPI
648 chuckv 246 eRow(i) = eRow(i) + pot*0.5
649     eCol(i) = eCol(i) + pot*0.5
650 chuckv 230 #else
651 chuckv 246 pe = pe + pot
652 chuckv 230 #endif
653 chuckv 281
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 chuckv 253 #ifdef IS_MPI
663 chuckv 281 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 chuckv 230
699    
700 chuckv 253 #ifdef IS_MPI
701 chuckv 230 !!distribute forces
702 chuckv 261
703 chuckv 253 call scatter(fRow,f,plan_row3d)
704 chuckv 230
705 chuckv 253 call scatter(fCol,fMPITemp,plan_col3d)
706 chuckv 246
707 chuckv 230 do i = 1,nlocal
708 chuckv 253 f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
709 chuckv 230 end do
710    
711 chuckv 261
712 chuckv 230
713     if (do_pot) then
714 chuckv 281 ! scatter/gather pot_row into the members of my column
715 chuckv 253 call scatter(eRow,eTemp,plan_row)
716 chuckv 230
717     ! scatter/gather pot_local into all other procs
718     ! add resultant to get total pot
719     do i = 1, nlocal
720 chuckv 253 pe_local = pe_local + eTemp(i)
721 chuckv 230 enddo
722     if (newtons_thrd) then
723 chuckv 253 eTemp = 0.0E0_DP
724     call scatter(eCol,eTemp,plan_col)
725 chuckv 230 do i = 1, nlocal
726 chuckv 253 pe_local = pe_local + eTemp(i)
727 chuckv 230 enddo
728     endif
729 chuckv 264 pe = pe_local
730 chuckv 230 endif
731 chuckv 281
732 chuckv 230 #endif
733    
734 chuckv 246 potE = pe
735 chuckv 230
736 chuckv 281
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 chuckv 222 end subroutine do_lj_ff
748    
749 chuckv 239 !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
750 chuckv 230 !! derivatives.
751     subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
752     ! arguments
753     !! Length of vector between particles
754     real( kind = dp ), intent(in) :: r
755     !! Potential Energy
756     real( kind = dp ), intent(out) :: pot
757     !! Derivatve wrt postion
758     real( kind = dp ), intent(out) :: dudr
759     !! Second Derivative, optional, used mainly for normal mode calculations.
760     real( kind = dp ), intent(out), optional :: d2
761    
762 chuckv 246 type (lj_atype), pointer :: atype1
763     type (lj_atype), pointer :: atype2
764 chuckv 222
765 chuckv 230 integer, intent(out), optional :: status
766 chuckv 222
767 chuckv 230 ! local Variables
768     real( kind = dp ) :: sigma
769     real( kind = dp ) :: sigma2
770     real( kind = dp ) :: sigma6
771 chuckv 246 real( kind = dp ) :: epsilon
772 chuckv 230
773     real( kind = dp ) :: rcut
774     real( kind = dp ) :: rcut2
775     real( kind = dp ) :: rcut6
776     real( kind = dp ) :: r2
777     real( kind = dp ) :: r6
778    
779     real( kind = dp ) :: t6
780     real( kind = dp ) :: t12
781     real( kind = dp ) :: tp6
782     real( kind = dp ) :: tp12
783     real( kind = dp ) :: delta
784    
785     logical :: doSec = .false.
786    
787     integer :: errorStat
788    
789     !! Optional Argument Checking
790     ! Check to see if we need to do second derivatives
791    
792     if (present(d2)) doSec = .true.
793     if (present(status)) status = 0
794    
795     ! Look up the correct parameters in the mixing matrix
796 chuckv 246 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 chuckv 230
801    
802 chuckv 253
803    
804 chuckv 230 call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
805    
806     r2 = r * r
807     r6 = r2 * r2 * r2
808    
809     t6 = sigma6/ r6
810     t12 = t6 * t6
811    
812    
813    
814     tp6 = sigma6 / rcut6
815     tp12 = tp6*tp6
816    
817     delta = -4.0E0_DP*epsilon * (tp12 - tp6)
818    
819     if (r.le.rcut) then
820 chuckv 246 pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
821 chuckv 230 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 chuckv 246 pot = 0.0E0_DP
825 chuckv 230 dudr = 0.0E0_DP
826     if(doSec) d2 = 0.0E0_DP
827     endif
828    
829     return
830    
831    
832    
833     end subroutine getLjPot
834    
835    
836 chuckv 239 !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
837 chuckv 230 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 chuckv 281 character(len = getStringLen()) :: thisMixingRule
843 chuckv 230 integer, optional :: status
844    
845 chuckv 281 !! get the mixing rules from the simulation
846     thisMixingRule = returnMixingRules()
847 chuckv 230 myMixParam = 0.0_dp
848    
849     if (present(status)) status = 0
850 chuckv 281 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 chuckv 230 case default
862     status = -1
863     end select
864     end function calcLJMix
865    
866    
867    
868 chuckv 215 end module lj_ff