ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
Revision: 252
Committed: Tue Jan 28 22:16:55 2003 UTC (21 years, 5 months ago) by chuckv
File size: 20712 byte(s)
Log Message:
Force loops seems to work, velocitize never being called....

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