ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/lj_FF.F90
Revision: 285
Committed: Wed Feb 26 18:45:57 2003 UTC (21 years, 6 months ago) by mmeineke
File size: 23542 byte(s)
Log Message:
OOPSE has been braought up to date with the mdtools devfelopment tree. mdtools should no longer be used. All development should take place in the OOPSE tree.

File Contents

# User Rev Content
1 mmeineke 270 !! 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 mmeineke 285 !! @version $Id: lj_FF.F90,v 1.2 2003-02-26 18:45:57 mmeineke Exp $, $Date: 2003-02-26 18:45:57 $, $Name: not supported by cvs2svn $, $Revision: 1.2 $
6 mmeineke 270
7    
8    
9     module lj_ff
10     use simulation
11     use definitions
12     use generic_atypes
13     #ifdef IS_MPI
14     use mpiSimulation
15     #endif
16     implicit none
17     PRIVATE
18    
19     !! Number of lj_atypes in lj_atype_list
20     integer, save :: n_lj_atypes = 0
21    
22     !! Global list of lj atypes in simulation
23     type (lj_atype), pointer :: ljListHead => null()
24     type (lj_atype), pointer :: ljListTail => null()
25    
26    
27     !! LJ mixing array
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     logical, save :: firstTime = .True.
40    
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    
56     !! Public methods and data
57     public :: new_lj_atype
58     public :: do_lj_ff
59     public :: getLjPot
60     public :: init_ljFF
61    
62    
63    
64    
65     contains
66    
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) :: epsilon
71     real( kind = dp ), intent(in) :: sigma
72     integer, intent(in) :: ident
73     integer, intent(out) :: status
74    
75     type (lj_atype), pointer :: newLJ_atype
76     integer :: alloc_error
77     integer :: atype_counter = 0
78     integer :: alloc_size
79     integer :: err_stat
80     status = 0
81    
82    
83    
84     ! allocate a new atype
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     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     newLJ_atype%atype_ident = ident
100     newLJ_atype%atype_number = n_lj_atypes + 1
101    
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     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     integer :: alloc_stat
124    
125     integer :: thisStat
126     integer :: i
127    
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    
138    
139    
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     !! 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    
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     !! 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    
255    
256    
257    
258    
259    
260     subroutine createMixingList(status)
261     integer :: listSize
262     integer :: status
263     integer :: i
264     integer :: j
265    
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     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     status = -1
283     return
284     end if
285    
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    
338     end do
339    
340     end subroutine createMixingList
341    
342    
343    
344    
345    
346    
347    
348    
349     !! FORCE routine Calculates Lennard Jones forces.
350     !------------------------------------------------------------->
351 mmeineke 285 subroutine do_lj_ff(q,f,potE,tau,do_pot)
352 mmeineke 270 !! 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 mmeineke 285 !! Stress Tensor
357     real( kind = dp), dimension(9) :: tau
358     real( kind = dp), dimension(9) :: tauTemp
359 mmeineke 270 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 mmeineke 285
366    
367    
368    
369    
370 mmeineke 270 #ifdef IS_MPI
371     real( kind = DP ) :: pot_local
372 mmeineke 285
373 mmeineke 270 !! Local arrays needed for MPI
374 mmeineke 285 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 mmeineke 270
377 mmeineke 285 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 mmeineke 270
381 mmeineke 285 real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
382     real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
383 mmeineke 270
384 mmeineke 285 real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
385 mmeineke 270
386 mmeineke 285 #endif
387 mmeineke 270
388    
389 mmeineke 285
390 mmeineke 270 real( kind = DP ) :: pe
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 mmeineke 285 real( kind = dp ) :: fx,fy,fz
400     real( kind = DP ) :: drdx, drdy, drdz
401 mmeineke 270 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 mmeineke 285 !! should we calculate the stress tensor
414     logical :: do_stress = .false.
415 mmeineke 270
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 mmeineke 285 !! Find ensemble
435     if (isEnsemble("NPT")) do_stress = .true.
436 mmeineke 270
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    
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     !--------------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     pe = 0.0E0_DP
463    
464     #else
465     fRow = 0.0E0_DP
466     fCol = 0.0E0_DP
467    
468     pe_local = 0.0E0_DP
469    
470     eRow = 0.0E0_DP
471     eCol = 0.0E0_DP
472     eTemp = 0.0E0_DP
473     #endif
474    
475     ! communicate MPI positions
476     #ifdef IS_MPI
477     call gather(q,qRow,plan_row3d)
478     call gather(q,qCol,plan_col3d)
479     #endif
480    
481    
482     if (update_nlist) then
483    
484     ! save current configuration, contruct neighbor list,
485     ! and calculate forces
486     call save_nlist(q)
487    
488     nlist = 0
489    
490    
491    
492     do i = 1, nrow
493     point(i) = nlist + 1
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)
505     rzi = q(3,i)
506     #endif
507    
508     inner: do j = j_start, ncol
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
516     else
517     if (mod(tag_i + tag_j,2) == 1) cycle inner
518     endif
519     endif
520    
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     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)
529    
530     #endif
531     rijsq = rxij*rxij + ryij*ryij + rzij*rzij
532    
533     #ifdef IS_MPI
534     if (rijsq <= rlistsq .AND. &
535     tag_j /= tag_i) then
536     #else
537    
538     if (rijsq < rlistsq) then
539     #endif
540    
541     nlist = nlist + 1
542     if (nlist > size(list)) then
543     !! "Change how nlist size is done"
544     write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
545     endif
546     list(nlist) = j
547    
548    
549     if (rijsq < rcutsq) then
550    
551     r = dsqrt(rijsq)
552    
553     call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
554    
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
560     #endif
561    
562 mmeineke 285 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 mmeineke 270 #ifdef IS_MPI
571 mmeineke 285 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 mmeineke 270 enddo
601    
602     #ifdef IS_MPI
603     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     #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 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     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    
642     if (rijsq < rcutsq) then
643    
644     r = dsqrt(rijsq)
645    
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     pe = pe + pot
652     #endif
653 mmeineke 285
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 mmeineke 270 #ifdef IS_MPI
663 mmeineke 285 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 mmeineke 270
699    
700     #ifdef IS_MPI
701     !!distribute forces
702    
703     call scatter(fRow,f,plan_row3d)
704    
705     call scatter(fCol,fMPITemp,plan_col3d)
706    
707     do i = 1,nlocal
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 mmeineke 285 ! scatter/gather pot_row into the members of my column
715 mmeineke 270 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     pe_local = pe_local + eTemp(i)
721     enddo
722     if (newtons_thrd) then
723     eTemp = 0.0E0_DP
724     call scatter(eCol,eTemp,plan_col)
725     do i = 1, nlocal
726     pe_local = pe_local + eTemp(i)
727     enddo
728     endif
729     pe = pe_local
730     endif
731 mmeineke 285
732 mmeineke 270 #endif
733    
734     potE = pe
735    
736 mmeineke 285
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 mmeineke 270 end subroutine do_lj_ff
748    
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
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     type (lj_atype), pointer :: atype1
763     type (lj_atype), pointer :: atype2
764    
765     integer, intent(out), optional :: status
766    
767     ! local Variables
768     real( kind = dp ) :: sigma
769     real( kind = dp ) :: sigma2
770     real( kind = dp ) :: sigma6
771     real( kind = dp ) :: epsilon
772    
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     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    
803    
804     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     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     pot = 0.0E0_DP
825     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     !! 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 mmeineke 285 character(len = getStringLen()) :: thisMixingRule
843 mmeineke 270 integer, optional :: status
844    
845 mmeineke 285 !! get the mixing rules from the simulation
846     thisMixingRule = returnMixingRules()
847 mmeineke 270 myMixParam = 0.0_dp
848    
849     if (present(status)) status = 0
850 mmeineke 285 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 mmeineke 270 case default
862     status = -1
863     end select
864     end function calcLJMix
865    
866    
867    
868     end module lj_ff