ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
Revision: 258
Committed: Thu Jan 30 22:29:37 2003 UTC (21 years, 5 months ago) by chuckv
File size: 21226 byte(s)
Log Message:
*** empty log message ***

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 258 !! @version $Id: lj_FF.F90,v 1.15 2003-01-30 22:29:37 chuckv Exp $, $Date: 2003-01-30 22:29:37 $, $Name: not supported by cvs2svn $, $Revision: 1.15 $
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 230 #ifdef IS_MPI
128 chuckv 239 integer, allocatable, dimension(:) :: identRow
129     integer, allocatable, dimension(:) :: identCol
130     integer :: nrow
131     integer :: ncol
132     #endif
133     status = 0
134 chuckv 254
135    
136 chuckv 258
137 chuckv 254
138 chuckv 239 !! if were're not in MPI, we just update ljatypePtrList
139     #ifndef IS_MPI
140 chuckv 247 call create_IdentPtrlst(ident,ljListHead,identPtrList,thisStat)
141 chuckv 239 if ( thisStat /= 0 ) then
142     status = -1
143     return
144     endif
145 chuckv 247
146 chuckv 239 !! Allocate pointer lists
147     allocate(point(nComponents),stat=alloc_stat)
148     if (alloc_stat /=0) then
149     status = -1
150     return
151     endif
152    
153     allocate(list(nComponents*listMultiplier),stat=alloc_stat)
154     if (alloc_stat /=0) then
155     status = -1
156     return
157     endif
158 chuckv 230
159 chuckv 239 ! if were're in MPI, we also have to worry about row and col lists
160     #else
161 chuckv 254
162 chuckv 239 ! We can only set up forces if mpiSimulation has been setup.
163     if (.not. isMPISimSet()) then
164 chuckv 254 write(default_error,*) "MPI is not set"
165 chuckv 239 status = -1
166     return
167     endif
168 chuckv 254 nrow = getNrow(plan_row)
169     ncol = getNcol(plan_col)
170 chuckv 258
171 chuckv 239 !! Allocate temperary arrays to hold gather information
172     allocate(identRow(nrow),stat=alloc_stat)
173     if (alloc_stat /= 0 ) then
174     status = -1
175     return
176     endif
177 chuckv 215
178 chuckv 239 allocate(identCol(ncol),stat=alloc_stat)
179     if (alloc_stat /= 0 ) then
180     status = -1
181     return
182     endif
183 chuckv 254
184 chuckv 239 !! Gather idents into row and column idents
185 chuckv 254
186 chuckv 239 call gather(ident,identRow,plan_row)
187     call gather(ident,identCol,plan_col)
188 chuckv 258
189 chuckv 254
190 chuckv 239 !! Create row and col pointer lists
191 chuckv 254
192     call create_IdentPtrlst(identRow,ljListHead,identPtrListRow,thisStat)
193 chuckv 239 if (thisStat /= 0 ) then
194     status = -1
195     return
196     endif
197    
198 chuckv 254 call create_IdentPtrlst(identCol,ljListHead,identPtrListColumn,thisStat)
199 chuckv 239 if (thisStat /= 0 ) then
200     status = -1
201     return
202     endif
203 chuckv 258 write(*,*) "After createIdent row-col lists"
204 chuckv 239 !! free temporary ident arrays
205 chuckv 258 if (allocated(identCol)) then
206     deallocate(identCol)
207     end if
208     if (allocated(identCol)) then
209     deallocate(identRow)
210     endif
211 chuckv 239
212     !! Allocate neighbor lists for mpi simulations.
213     if (.not. allocated(point)) then
214     allocate(point(nrow),stat=alloc_stat)
215     if (alloc_stat /=0) then
216     status = -1
217     return
218     endif
219    
220     allocate(list(ncol*listMultiplier),stat=alloc_stat)
221     if (alloc_stat /=0) then
222     status = -1
223     return
224     endif
225     else
226     deallocate(list)
227     deallocate(point)
228     allocate(point(nrow),stat=alloc_stat)
229     if (alloc_stat /=0) then
230     status = -1
231     return
232     endif
233    
234     allocate(list(ncol*listMultiplier),stat=alloc_stat)
235     if (alloc_stat /=0) then
236     status = -1
237     return
238     endif
239     endif
240    
241 chuckv 230 #endif
242 chuckv 239
243 chuckv 247 call createMixingList(thisStat)
244     if (thisStat /= 0) then
245     status = -1
246     return
247     endif
248 chuckv 239 isljFFinit = .true.
249    
250 chuckv 230 end subroutine init_ljFF
251    
252 chuckv 239
253    
254    
255    
256 chuckv 230
257 chuckv 247 subroutine createMixingList(status)
258     integer :: listSize
259     integer :: status
260 chuckv 230 integer :: i
261 chuckv 247 integer :: j
262 chuckv 230
263 chuckv 247 integer :: outerCounter = 0
264     integer :: innerCounter = 0
265     type (lj_atype), pointer :: tmpPtrOuter => null()
266     type (lj_atype), pointer :: tmpPtrInner => null()
267     status = 0
268 chuckv 230
269 chuckv 247 listSize = getListLen(ljListHead)
270     if (listSize == 0) then
271     status = -1
272     return
273     end if
274    
275    
276     if (.not. associated(ljMixed)) then
277     allocate(ljMixed(listSize,listSize))
278 chuckv 230 else
279 chuckv 247 status = -1
280     return
281     end if
282 chuckv 230
283 chuckv 247
284 chuckv 252
285 chuckv 247 tmpPtrOuter => ljListHead
286     tmpPtrInner => tmpPtrOuter%next
287     do while (associated(tmpPtrOuter))
288     outerCounter = outerCounter + 1
289     ! do self mixing rule
290     ljMixed(outerCounter,outerCounter)%sigma = tmpPtrOuter%sigma
291    
292     ljMixed(outerCounter,outerCounter)%sigma2 = ljMixed(outerCounter,outerCounter)%sigma &
293     * ljMixed(outerCounter,outerCounter)%sigma
294    
295     ljMixed(outerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,outerCounter)%sigma2 &
296     * ljMixed(outerCounter,outerCounter)%sigma2 &
297     * ljMixed(outerCounter,outerCounter)%sigma2
298    
299     ljMixed(outerCounter,outerCounter)%epsilon = tmpPtrOuter%epsilon
300    
301     innerCounter = outerCounter + 1
302     do while (associated(tmpPtrInner))
303    
304     ljMixed(outerCounter,innerCounter)%sigma = &
305     calcLJMix("sigma",tmpPtrOuter%sigma, &
306     tmpPtrInner%sigma)
307    
308     ljMixed(outerCounter,innerCounter)%sigma2 = &
309     ljMixed(outerCounter,innerCounter)%sigma &
310     * ljMixed(outerCounter,innerCounter)%sigma
311    
312     ljMixed(outerCounter,innerCounter)%sigma6 = &
313     ljMixed(outerCounter,innerCounter)%sigma2 &
314     * ljMixed(outerCounter,innerCounter)%sigma2 &
315     * ljMixed(outerCounter,innerCounter)%sigma2
316    
317     ljMixed(outerCounter,innerCounter)%epsilon = &
318     calcLJMix("epsilon",tmpPtrOuter%epsilon, &
319     tmpPtrInner%epsilon)
320     ljMixed(innerCounter,outerCounter)%sigma = ljMixed(outerCounter,innerCounter)%sigma
321     ljMixed(innerCounter,outerCounter)%sigma2 = ljMixed(outerCounter,innerCounter)%sigma2
322     ljMixed(innerCounter,outerCounter)%sigma6 = ljMixed(outerCounter,innerCounter)%sigma6
323     ljMixed(innerCounter,outerCounter)%epsilon = ljMixed(outerCounter,innerCounter)%epsilon
324    
325    
326     tmpPtrInner => tmpPtrInner%next
327     innerCounter = innerCounter + 1
328     end do
329     ! advance pointers
330     tmpPtrOuter => tmpPtrOuter%next
331     if (associated(tmpPtrOuter)) then
332     tmpPtrInner => tmpPtrOuter%next
333 chuckv 230 endif
334    
335     end do
336    
337 chuckv 247 end subroutine createMixingList
338 chuckv 230
339    
340 chuckv 246
341 chuckv 230
342    
343 chuckv 246
344    
345    
346 chuckv 239 !! FORCE routine Calculates Lennard Jones forces.
347 chuckv 230 !------------------------------------------------------------->
348     subroutine do_lj_ff(q,f,potE,do_pot)
349 chuckv 246 !! Position array provided by C, dimensioned by getNlocal
350     real ( kind = dp ), dimension(3,getNlocal()) :: q
351     !! Force array provided by C, dimensioned by getNlocal
352     real ( kind = dp ), dimension(3,getNlocal()) :: f
353 chuckv 222 real ( kind = dp ) :: potE
354 mmeineke 235 logical ( kind = 2) :: do_pot
355 chuckv 239
356     type(lj_atype), pointer :: ljAtype_i
357     type(lj_atype), pointer :: ljAtype_j
358    
359 chuckv 253 #ifdef IS_MPI
360 chuckv 254 real( kind = DP ), dimension(3,getNcol(plan_col)) :: efr
361 chuckv 230 real( kind = DP ) :: pot_local
362     #else
363 chuckv 246 real( kind = DP ), dimension(3,getNlocal()) :: efr
364 chuckv 230 #endif
365    
366 chuckv 247 !! Local arrays needed for MPI
367     #ifdef IS_MPI
368 chuckv 254 real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow
369     real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol
370 chuckv 247
371 chuckv 254 real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow
372     real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol
373     real(kind = dp), dimension(3,getNlocal()) :: fMPITemp
374 chuckv 247
375 chuckv 254 real(kind = dp), dimension(getNrow(plan_row)) :: eRow
376     real(kind = dp), dimension(getNcol(plan_col)) :: eCol
377 chuckv 247
378     real(kind = dp), dimension(getNlocal()) :: eTemp
379     #endif
380    
381    
382    
383 chuckv 230 real( kind = DP ) :: pe
384 chuckv 246 logical :: update_nlist
385 chuckv 216
386 chuckv 232
387 chuckv 230 integer :: i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
388     integer :: nlist
389     integer :: j_start
390     integer :: tag_i,tag_j
391     real( kind = DP ) :: r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
392     real( kind = DP ) :: rxi, ryi, rzi, rxij, ryij, rzij, rijsq
393 chuckv 246 real( kind = DP ) :: rlistsq, rcutsq,rlist,rcut
394 chuckv 222
395 chuckv 246 ! a rig that need to be fixed.
396     #ifdef IS_MPI
397     logical :: newtons_thrd = .true.
398     real( kind = dp ) :: pe_local
399     integer :: nlocal
400     #endif
401 chuckv 230 integer :: nrow
402     integer :: ncol
403 chuckv 246 integer :: natoms
404 chuckv 222
405 chuckv 253
406    
407    
408 chuckv 246 ! Make sure we are properly initialized.
409 chuckv 239 if (.not. isljFFInit) then
410     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
411     return
412     endif
413 chuckv 246 #ifdef IS_MPI
414     if (.not. isMPISimSet()) then
415     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
416     return
417     endif
418     #endif
419 chuckv 222
420 chuckv 246 !! initialize local variables
421     natoms = getNlocal()
422     call getRcut(rcut,rcut2=rcutsq)
423     call getRlist(rlist,rlistsq)
424 chuckv 253
425 chuckv 230 #ifndef IS_MPI
426     nrow = natoms - 1
427     ncol = natoms
428     #else
429 chuckv 239 nrow = getNrow(plan_row)
430     ncol = getNcol(plan_col)
431 chuckv 246 nlocal = natoms
432 chuckv 230 j_start = 1
433     #endif
434 chuckv 222
435 chuckv 239
436 chuckv 246 !! See if we need to update neighbor lists
437     call check(q,update_nlist)
438 chuckv 253 if (firstTime) then
439     update_nlist = .true.
440     firstTime = .false.
441     endif
442 chuckv 239
443     !--------------WARNING...........................
444     ! Zero variables, NOTE:::: Forces are zeroed in C
445     ! Zeroing them here could delete previously computed
446     ! Forces.
447     !------------------------------------------------
448 chuckv 230 #ifndef IS_MPI
449 chuckv 246 ! nloops = nloops + 1
450     pe = 0.0E0_DP
451    
452 chuckv 230 #else
453 chuckv 253 fRow = 0.0E0_DP
454     fCol = 0.0E0_DP
455 chuckv 230
456 chuckv 246 pe_local = 0.0E0_DP
457 chuckv 230
458 chuckv 246 eRow = 0.0E0_DP
459     eCol = 0.0E0_DP
460     eTemp = 0.0E0_DP
461 chuckv 230 #endif
462     efr = 0.0E0_DP
463    
464     ! communicate MPI positions
465 chuckv 253 #ifdef IS_MPI
466     call gather(q,qRow,plan_row3d)
467     call gather(q,qCol,plan_col3d)
468 chuckv 230 #endif
469    
470    
471     if (update_nlist) then
472    
473     ! save current configuration, contruct neighbor list,
474     ! and calculate forces
475 chuckv 246 call save_nlist(q)
476 chuckv 230
477     nlist = 0
478    
479 chuckv 253
480 chuckv 230
481     do i = 1, nrow
482     point(i) = nlist + 1
483 chuckv 253 #ifdef IS_MPI
484 chuckv 239 ljAtype_i => identPtrListRow(i)%this
485     tag_i = tagRow(i)
486     rxi = qRow(1,i)
487     ryi = qRow(2,i)
488     rzi = qRow(3,i)
489 chuckv 230 #else
490 chuckv 239 ljAtype_i => identPtrList(i)%this
491 chuckv 230 j_start = i + 1
492     rxi = q(1,i)
493     ryi = q(2,i)
494     rzi = q(3,i)
495     #endif
496    
497     inner: do j = j_start, ncol
498 chuckv 253 #ifdef IS_MPI
499 chuckv 239 ! Assign identity pointers and tags
500     ljAtype_j => identPtrListColumn(j)%this
501 chuckv 254 tag_j = tagColumn(j)
502 chuckv 230 if (newtons_thrd) then
503     if (tag_i <= tag_j) then
504     if (mod(tag_i + tag_j,2) == 0) cycle inner
505     else
506     if (mod(tag_i + tag_j,2) == 1) cycle inner
507     endif
508     endif
509    
510 chuckv 239 rxij = wrap(rxi - qCol(1,j), 1)
511     ryij = wrap(ryi - qCol(2,j), 2)
512     rzij = wrap(rzi - qCol(3,j), 3)
513 chuckv 230 #else
514 chuckv 239 ljAtype_j => identPtrList(j)%this
515 chuckv 230 rxij = wrap(rxi - q(1,j), 1)
516     ryij = wrap(ryi - q(2,j), 2)
517     rzij = wrap(rzi - q(3,j), 3)
518    
519     #endif
520     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
521    
522 chuckv 253 #ifdef IS_MPI
523 chuckv 246 if (rijsq <= rlistsq .AND. &
524 chuckv 230 tag_j /= tag_i) then
525     #else
526 chuckv 253
527 chuckv 246 if (rijsq < rlistsq) then
528 chuckv 230 #endif
529    
530     nlist = nlist + 1
531     if (nlist > size(list)) then
532 chuckv 246 !! "Change how nlist size is done"
533 chuckv 239 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
534 chuckv 230 endif
535     list(nlist) = j
536    
537 chuckv 253
538 chuckv 230 if (rijsq < rcutsq) then
539    
540     r = dsqrt(rijsq)
541    
542 chuckv 239 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
543 chuckv 230
544 chuckv 253 #ifdef IS_MPI
545 chuckv 246 eRow(i) = eRow(i) + pot*0.5
546     eCol(i) = eCol(i) + pot*0.5
547 chuckv 230 #else
548 chuckv 253 pe = pe + pot
549 chuckv 230 #endif
550    
551     efr(1,j) = -rxij
552     efr(2,j) = -ryij
553     efr(3,j) = -rzij
554    
555     do dim = 1, 3
556    
557    
558     drdx1 = efr(dim,j) / r
559     ftmp = dudr * drdx1
560    
561    
562 chuckv 253 #ifdef IS_MPI
563 chuckv 239 fCol(dim,j) = fCol(dim,j) - ftmp
564     fRow(dim,i) = fRow(dim,i) + ftmp
565 chuckv 230 #else
566    
567     f(dim,j) = f(dim,j) - ftmp
568     f(dim,i) = f(dim,i) + ftmp
569    
570     #endif
571     enddo
572     endif
573     endif
574     enddo inner
575     enddo
576    
577 chuckv 253 #ifdef IS_MPI
578 chuckv 230 point(nrow + 1) = nlist + 1
579     #else
580     point(natoms) = nlist + 1
581     #endif
582    
583     else
584    
585     ! use the list to find the neighbors
586     do i = 1, nrow
587     JBEG = POINT(i)
588     JEND = POINT(i+1) - 1
589     ! check thiat molecule i has neighbors
590     if (jbeg .le. jend) then
591 chuckv 253 #ifdef IS_MPI
592 chuckv 239 ljAtype_i => identPtrListRow(i)%this
593     rxi = qRow(1,i)
594     ryi = qRow(2,i)
595     rzi = qRow(3,i)
596 chuckv 230 #else
597 chuckv 239 ljAtype_i => identPtrList(i)%this
598 chuckv 230 rxi = q(1,i)
599     ryi = q(2,i)
600     rzi = q(3,i)
601     #endif
602     do jnab = jbeg, jend
603     j = list(jnab)
604 chuckv 253 #ifdef IS_MPI
605 chuckv 239 ljAtype_j = identPtrListColumn(j)%this
606 chuckv 254 rxij = wrap(rxi - qCol(1,j), 1)
607     ryij = wrap(ryi - qCol(2,j), 2)
608     rzij = wrap(rzi - qCol(3,j), 3)
609 chuckv 230 #else
610 chuckv 239 ljAtype_j = identPtrList(j)%this
611     rxij = wrap(rxi - q(1,j), 1)
612     ryij = wrap(ryi - q(2,j), 2)
613     rzij = wrap(rzi - q(3,j), 3)
614 chuckv 230 #endif
615     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
616    
617     if (rijsq < rcutsq) then
618    
619     r = dsqrt(rijsq)
620    
621 chuckv 239 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
622 chuckv 253 #ifdef IS_MPI
623 chuckv 246 eRow(i) = eRow(i) + pot*0.5
624     eCol(i) = eCol(i) + pot*0.5
625 chuckv 230 #else
626 chuckv 246 pe = pe + pot
627 chuckv 230 #endif
628    
629    
630     efr(1,j) = -rxij
631     efr(2,j) = -ryij
632     efr(3,j) = -rzij
633    
634     do dim = 1, 3
635    
636     drdx1 = efr(dim,j) / r
637     ftmp = dudr * drdx1
638 chuckv 253 #ifdef IS_MPI
639 chuckv 239 fCol(dim,j) = fCol(dim,j) - ftmp
640     fRow(dim,i) = fRow(dim,i) + ftmp
641 chuckv 230 #else
642     f(dim,j) = f(dim,j) - ftmp
643     f(dim,i) = f(dim,i) + ftmp
644     #endif
645     enddo
646     endif
647     enddo
648     endif
649     enddo
650     endif
651    
652    
653    
654 chuckv 253 #ifdef IS_MPI
655 chuckv 230 !!distribute forces
656 chuckv 253 call scatter(fRow,f,plan_row3d)
657 chuckv 230
658 chuckv 253 call scatter(fCol,fMPITemp,plan_col3d)
659 chuckv 246
660 chuckv 230 do i = 1,nlocal
661 chuckv 253 f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
662 chuckv 230 end do
663    
664    
665    
666     if (do_pot) then
667     ! scatter/gather pot_row into the members of my column
668 chuckv 253 call scatter(eRow,eTemp,plan_row)
669 chuckv 230
670     ! scatter/gather pot_local into all other procs
671     ! add resultant to get total pot
672     do i = 1, nlocal
673 chuckv 253 pe_local = pe_local + eTemp(i)
674 chuckv 230 enddo
675     if (newtons_thrd) then
676 chuckv 253 eTemp = 0.0E0_DP
677     call scatter(eCol,eTemp,plan_col)
678 chuckv 230 do i = 1, nlocal
679 chuckv 253 pe_local = pe_local + eTemp(i)
680 chuckv 230 enddo
681     endif
682     endif
683 chuckv 246 potE = pe_local
684 chuckv 230 #endif
685    
686 chuckv 246 potE = pe
687 chuckv 230
688 chuckv 253
689 chuckv 230
690 chuckv 253
691 chuckv 222 end subroutine do_lj_ff
692    
693 chuckv 239 !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
694 chuckv 230 !! derivatives.
695     subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
696     ! arguments
697     !! Length of vector between particles
698     real( kind = dp ), intent(in) :: r
699     !! Potential Energy
700     real( kind = dp ), intent(out) :: pot
701     !! Derivatve wrt postion
702     real( kind = dp ), intent(out) :: dudr
703     !! Second Derivative, optional, used mainly for normal mode calculations.
704     real( kind = dp ), intent(out), optional :: d2
705    
706 chuckv 246 type (lj_atype), pointer :: atype1
707     type (lj_atype), pointer :: atype2
708 chuckv 222
709 chuckv 230 integer, intent(out), optional :: status
710 chuckv 222
711 chuckv 230 ! local Variables
712     real( kind = dp ) :: sigma
713     real( kind = dp ) :: sigma2
714     real( kind = dp ) :: sigma6
715 chuckv 246 real( kind = dp ) :: epsilon
716 chuckv 230
717     real( kind = dp ) :: rcut
718     real( kind = dp ) :: rcut2
719     real( kind = dp ) :: rcut6
720     real( kind = dp ) :: r2
721     real( kind = dp ) :: r6
722    
723     real( kind = dp ) :: t6
724     real( kind = dp ) :: t12
725     real( kind = dp ) :: tp6
726     real( kind = dp ) :: tp12
727     real( kind = dp ) :: delta
728    
729     logical :: doSec = .false.
730    
731     integer :: errorStat
732    
733     !! Optional Argument Checking
734     ! Check to see if we need to do second derivatives
735    
736     if (present(d2)) doSec = .true.
737     if (present(status)) status = 0
738    
739     ! Look up the correct parameters in the mixing matrix
740 chuckv 246 sigma = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
741     sigma2 = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
742     sigma6 = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
743     epsilon = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
744 chuckv 230
745    
746 chuckv 253
747    
748 chuckv 230 call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
749    
750     r2 = r * r
751     r6 = r2 * r2 * r2
752    
753     t6 = sigma6/ r6
754     t12 = t6 * t6
755    
756    
757    
758     tp6 = sigma6 / rcut6
759     tp12 = tp6*tp6
760    
761     delta = -4.0E0_DP*epsilon * (tp12 - tp6)
762    
763     if (r.le.rcut) then
764 chuckv 246 pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
765 chuckv 230 dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
766     if(doSec) d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
767     else
768 chuckv 246 pot = 0.0E0_DP
769 chuckv 230 dudr = 0.0E0_DP
770     if(doSec) d2 = 0.0E0_DP
771     endif
772    
773     return
774    
775    
776    
777     end subroutine getLjPot
778    
779    
780 chuckv 239 !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
781 chuckv 230 function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
782     character(len=*) :: thisParam
783     real(kind = dp) :: param1
784     real(kind = dp) :: param2
785     real(kind = dp ) :: myMixParam
786     integer, optional :: status
787    
788    
789     myMixParam = 0.0_dp
790    
791     if (present(status)) status = 0
792    
793     select case (thisParam)
794    
795     case ("sigma")
796     myMixParam = 0.5_dp * (param1 + param2)
797 chuckv 246 case ("epsilon")
798 chuckv 230 myMixParam = sqrt(param1 * param2)
799     case default
800     status = -1
801     end select
802    
803     end function calcLJMix
804    
805    
806    
807 chuckv 215 end module lj_ff