ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
Revision: 240
Committed: Wed Jan 22 21:45:20 2003 UTC (21 years, 5 months ago) by chuckv
File size: 23847 byte(s)
Log Message:
Added init function to c++ force module.

File Contents

# Content
1 !! Calculates Long Range forces Lennard-Jones interactions.
2 !! Corresponds to the force field defined in lj_FF.cpp
3 !! @author Charles F. Vardeman II
4 !! @author Matthew Meineke
5 !! @version $Id: lj_FF.F90,v 1.9 2003-01-22 21:45:20 chuckv Exp $, $Date: 2003-01-22 21:45:20 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
6
7
8
9 module lj_ff
10 use simulation
11 use definitions, ONLY : dp, ndim
12 #ifdef IS_MPI
13 use mpiSimulation
14 #endif
15 implicit none
16 PRIVATE
17
18 !! Number of lj_atypes in lj_atype_list
19 integer, save :: n_lj_atypes = 0
20
21 !! Starting Size for ljMixed Array
22 integer, parameter :: ljMixed_blocksize = 10
23
24 !! Basic atom type for a Lennard-Jones Atom.
25 type, public :: lj_atype
26 private
27 sequence
28 !! Unique number for place in linked list
29 integer :: atype_number = 0
30 !! Unique indentifier number (ie atomic no, etc)
31 integer :: atype_ident = 0
32 !! Mass of Particle
33 real ( kind = dp ) :: mass = 0.0_dp
34 !! Lennard-Jones epslon
35 real ( kind = dp ) :: epslon = 0.0_dp
36 !! Lennard-Jones Sigma
37 real ( kind = dp ) :: sigma = 0.0_dp
38 !! Lennard-Jones Sigma Squared
39 real ( kind = dp ) :: sigma2 = 0.0_dp
40 !! Lennard-Jones Sigma to sixth
41 real ( kind = dp ) :: sigma6 = 0.0_dp
42 !! Pointer for linked list creation
43 type (lj_atype), pointer :: next => null()
44 end type lj_atype
45
46 !! Pointer type for atype ident array
47 type, public :: lj_atypePtr
48 type (lj_atype), pointer :: this => null()
49 end type lj_atypePtr
50
51 !! Global list of lj atypes in simulation
52 type (lj_atype), pointer :: lj_atype_list => null()
53 !! LJ mixing array
54 type (lj_atype), dimension(:,:), allocatable, pointer :: ljMixed =>null()
55 !! identity pointer list for force loop.
56 type (lj_atypePtr), dimension(:), allocatable :: identPtrList
57
58
59 !! Neighbor list and commom arrays
60 !! This should eventally get moved to a neighbor list type
61 integer, allocatable, dimension(:) :: point
62 integer, allocatable, dimension(:) :: list
63 integer, parameter :: listMultiplier = 80
64 integer :: nListAllocs = 0
65 integer, parameter :: maxListAllocs = 5
66
67 #ifdef IS_MPI
68 ! Universal routines: All types of force calculations will need these arrays
69 ! Arrays specific to a type of force calculation should be declared in that module.
70 real( kind = dp ), allocatable, dimension(:,:) :: qRow
71 real( kind = dp ), allocatable, dimension(:,:) :: qColumn
72
73 real( kind = dp ), allocatable, dimension(:,:) :: fRow
74 real( kind = dp ), allocatable, dimension(:,:) :: fColumn
75
76 type (lj_atypePtr), dimension(:), allocatable :: identPtrListRow
77 type (lj_atypePtr), dimension(:), allocatable :: identPtrListColumn
78 #endif
79
80
81
82 logical :: isljFFinit = .false.
83
84
85 !! Public methods and data
86 public :: new_lj_atype
87 public :: do_lj_ff
88 public :: getLjPot
89
90
91
92
93
94 contains
95
96 subroutine new_lj_atype(ident,mass,epslon,sigma,status)
97 real( kind = dp ), intent(in) :: mass
98 real( kind = dp ), intent(in) :: epslon
99 real( kind = dp ), intent(in) :: sigma
100 integer, intent(in) :: ident
101 integer, intent(out) :: status
102
103 type (lj_atype), pointer :: this_lj_atype
104 type (lj_atype), pointer :: lj_atype_ptr
105
106 type (lj_atype), allocatable, dimension(:,:), pointer :: thisMix
107 type (lj_atype), allocatable, dimension(:,:), pointer :: oldMix
108 integer :: alloc_error
109 integer :: atype_counter = 0
110 integer :: alloc_size
111
112 status = 0
113
114
115
116 ! allocate a new atype
117 allocate(this_lj_atype,stat=alloc_error)
118 if (alloc_error /= 0 ) then
119 status = -1
120 return
121 end if
122
123 ! assign our new lj_atype information
124 this_lj_atype%mass = mass
125 this_lj_atype%epslon = epslon
126 this_lj_atype%sigma = sigma
127 this_lj_atype%sigma2 = sigma * sigma
128 this_lj_atype%sigma6 = this_lj_atype%sigma2 * this_lj_atype%sigma2 &
129 * this_lj_atype%sigma2
130 ! assume that this atype will be successfully added
131 this_lj_atype%atype_ident = ident
132 this_lj_atype%number = n_lj_atypes + 1
133
134
135 ! First time through allocate a array of size ljMixed_blocksize
136 if(.not. associated(ljMixed)) then
137 allocate(thisMix(ljMixed_blocksize,ljMixed_blocksize))
138 if (alloc_error /= 0 ) then
139 status = -1
140 return
141 end if
142 ljMixed => thisMix
143 ! If we have outgrown ljMixed_blocksize, allocate a new matrix twice the size and
144 ! point ljMix at the new matrix.
145 else if( (n_lj_atypes + 1) > size(ljMixed)) then
146 alloc_size = 2*size(ljMix)
147 allocate(thisMix(alloc_size,alloc_size))
148 if (alloc_error /= 0 ) then
149 status = -1
150 return
151 end if
152 ! point oldMix at old ljMixed array
153 oldMix => ljMixed
154 ! Copy oldMix into new Mixed array
155 thisMix = oldMix
156 ! Point ljMixed at new array
157 ljMixed => thisMix
158 ! Free old array so we don't have a memory leak
159 deallocate(oldMix)
160 endif
161
162
163
164
165
166 ! Find bottom of atype master list
167 ! if lj_atype_list is null then we are at the top of the list.
168 if (.not. associated(lj_atype_list)) then
169 lj_atype_ptr => this_lj_atype
170 atype_counter = 1
171
172 else ! we need to find the bottom of the list to insert new atype
173 lj_atype_ptr => lj_atype_list%next
174 atype_counter = 1
175 find_end: do
176 if (.not. associated(lj_atype_ptr%next)) then
177 exit find_end
178 end if
179 ! Set up mixing for new atype and current atype in list
180 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma = &
181 calcLJMix("sigma",this_lj_atype%sigma, &
182 lj_atype_prt%sigma)
183
184 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 = &
185 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma &
186 * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma
187
188 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma6 = &
189 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
190 * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2 &
191 * ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%sigma2
192
193 ljMix(this_lj_atype%atype_number,lj_atype_ptr%atype_number)%epslon = &
194 calcLJMix("epslon",this_lj_atype%epslon, &
195 lj_atype_prt%epslon)
196
197 ! Advance to next pointer
198 lj_atype_ptr => lj_atype_ptr%next
199 atype_counter = atype_counter + 1
200
201 end do find_end
202 end if
203
204
205
206
207 ! Insert new atype at end of list
208 lj_atype_ptr => this_lj_atype
209 ! Increment number of atypes
210
211 n_lj_atypes = n_lj_atypes + 1
212
213 ! Set up self mixing
214
215 ljMix(n_lj_atypes,n_lj_atypes)%sigma = this_lj_atype%sigma
216
217 ljMix(n_lj_atypes,n_lj_atypes)%sigma2 = ljMix(n_lj_atypes,n_lj_atypes)%sigma &
218 * ljMix(n_lj_atypes,n_lj_atypes)%sigma
219
220 ljMix(n_lj_atypes,n_lj_atypes)%sigma6 = ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
221 * ljMix(n_lj_atypes,n_lj_atypes)%sigma2 &
222 * ljMix(n_lj_atypes,n_lj_atypes)%sigma2
223
224 ljMix(n_lj_atypes,n_lj_atypes)%epslon = this_lj_atype%epslon
225
226
227 end subroutine new_lj_atype
228
229
230 subroutine init_ljFF(nComponents,ident, status)
231 !! Number of components in ident array
232 integer, intent(inout) :: nComponents
233 !! Array of identities nComponents long corresponding to
234 !! ljatype ident.
235 integer, dimension(nComponents),intent(inout) :: ident
236 !! Result status, success = 0, error = -1
237 integer, intent(out) :: Status
238
239 integer :: thisStat
240 #ifdef IS_MPI
241 integer, allocatable, dimension(:) :: identRow
242 integer, allocatable, dimension(:) :: identCol
243 integer :: nrow
244 integer :: ncol
245 integer :: alloc_stat
246 #endif
247 status = 0
248
249 !! if were're not in MPI, we just update ljatypePtrList
250 #ifndef IS_MPI
251 call new_ljatypePtrList(nComponents,ident,identPtrList,thisStat)
252 if ( thisStat /= 0 ) then
253 status = -1
254 return
255 endif
256 !! Allocate pointer lists
257 allocate(point(nComponents),stat=alloc_stat)
258 if (alloc_stat /=0) then
259 status = -1
260 return
261 endif
262
263 allocate(list(nComponents*listMultiplier),stat=alloc_stat)
264 if (alloc_stat /=0) then
265 status = -1
266 return
267 endif
268
269 ! if were're in MPI, we also have to worry about row and col lists
270 #else
271 ! We can only set up forces if mpiSimulation has been setup.
272 if (.not. isMPISimSet()) then
273 status = -1
274 return
275 endif
276 nrow = getNrow()
277 ncol = getNcol()
278 !! Allocate temperary arrays to hold gather information
279 allocate(identRow(nrow),stat=alloc_stat)
280 if (alloc_stat /= 0 ) then
281 status = -1
282 return
283 endif
284
285 allocate(identCol(ncol),stat=alloc_stat)
286 if (alloc_stat /= 0 ) then
287 status = -1
288 return
289 endif
290 !! Gather idents into row and column idents
291 call gather(ident,identRow,plan_row)
292 call gather(ident,identCol,plan_col)
293
294 !! Create row and col pointer lists
295 call new_ljatypePtrList(nrow,identRow,identPtrListRow,thisStat)
296 if (thisStat /= 0 ) then
297 status = -1
298 return
299 endif
300
301 call new_ljatypePtrList(ncol,identCol,identPtrListCol,thisStat)
302 if (thisStat /= 0 ) then
303 status = -1
304 return
305 endif
306
307 !! free temporary ident arrays
308 deallocate(identCol)
309 deallocate(identRow)
310
311 !! Allocate Simulation arrays
312 !! NOTE: This bit of code should be fixed, it can cause large
313 !! memory fragmentation if call repeatedly
314
315 if (.not.allocated(qRow)) then
316 allocate(qRow(3,nrow),stat=alloc_stat)
317 if (alloc_stat /= 0 ) then
318 status = -1
319 return
320 endif
321 else
322 deallocate(qrow)
323 allocate(qRow(3,nrow),stat=alloc_stat)
324 if (alloc_stat /= 0 ) then
325 status = -1
326 return
327 endif
328 endif
329
330 if (.not.allocated(3,qCol)) then
331 allocate(qCol(ncol),stat=alloc_stat)
332 if (alloc_stat /= 0 ) then
333 status = -1
334 return
335 endif
336 else
337 deallocate(qCol)
338 allocate(qCol(3,ncol),stat=alloc_stat)
339 if (alloc_stat /= 0 ) then
340 status = -1
341 return
342 endif
343 endif
344
345 if (.not.allocated(fRow)) then
346 allocate(fRow(3,nrow),stat=alloc_stat)
347 if (alloc_stat /= 0 ) then
348 status = -1
349 return
350 endif
351 else
352 deallocate(fRow)
353 allocate(fRow(3,nrow),stat=alloc_stat)
354 if (alloc_stat /= 0 ) then
355 status = -1
356 return
357 endif
358 endif
359
360 if (.not.allocated(fCol)) then
361 allocate(fCol(3,ncol),stat=alloc_stat)
362 if (alloc_stat /= 0 ) then
363 status = -1
364 return
365 endif
366 else
367 deallocate(fCol)
368 allocate(fCol(3,ncol),stat=alloc_stat)
369 if (alloc_stat /= 0 ) then
370 status = -1
371 return
372 endif
373 endif
374 !! Allocate neighbor lists for mpi simulations.
375 if (.not. allocated(point)) then
376 allocate(point(nrow),stat=alloc_stat)
377 if (alloc_stat /=0) then
378 status = -1
379 return
380 endif
381
382 allocate(list(ncol*listMultiplier),stat=alloc_stat)
383 if (alloc_stat /=0) then
384 status = -1
385 return
386 endif
387 else
388 deallocate(list)
389 deallocate(point)
390 allocate(point(nrow),stat=alloc_stat)
391 if (alloc_stat /=0) then
392 status = -1
393 return
394 endif
395
396 allocate(list(ncol*listMultiplier),stat=alloc_stat)
397 if (alloc_stat /=0) then
398 status = -1
399 return
400 endif
401 endif
402
403 #endif
404
405
406 isljFFinit = .true.
407
408
409 end subroutine init_ljFF
410
411
412
413
414
415 !! Takes an ident array and creates an atype pointer list
416 !! based on those identities
417 subroutine new_ljatypePtrList(mysize,ident,PtrList,status)
418 integer, intent(in) :: mysize
419 integer, intent(in) :: ident
420 integer, optional :: status
421 type(lj_atypePtr), dimension(:) :: PtrList
422
423 integer :: thisIdent
424 integer :: i
425 integer :: alloc_error
426 type (lj_atype), pointer :: tmpPtr
427
428 if (present(status)) status = 0
429
430 ! First time through, allocate list
431 if (.not.(allocated)) then
432 allocate(PtrList(mysize))
433 else
434 ! We want to creat a new ident list so free old list
435 deallocate(PrtList)
436 allocate(PtrList(mysize))
437 endif
438
439 ! Match pointer list
440 do i = 1, mysize
441 thisIdent = ident(i)
442 call getLJatype(thisIdent,tmpPtr)
443
444 if (.not. associated(tmpPtr)) then
445 status = -1
446 return
447 endif
448
449 PtrList(i)%this => tmpPtr
450 end do
451
452 end subroutine new_ljatypePtrList
453
454 !! Finds a lj_atype based upon numerical ident
455 !! returns a null pointer if error
456 subroutine getLJatype(ident,ljAtypePtr)
457 integer, intent(in) :: ident
458 type (lj_atype), intent(out),pointer :: ljAtypePtr => null()
459
460 type (lj_atype), pointer :: tmplj_atype_ptr => null()
461
462 if(.not. associated(lj_atype_list)) return
463
464 ! Point at head of list.
465 tmplj_atype_ptr => lj_atype_list
466 find_ident: do
467 if (.not.associated(tmplj_atype_ptr)) then
468 exit find_ident
469 else if( lj_atype_ptr%atype_ident == ident)
470 ljAtypePtr => tmplj_atype_ptr
471 exit find_ident
472 endif
473 tmplj_atype_ptr => tmplj_atype_ptr%next
474 end do find_ident
475
476 end subroutine getLJatype
477
478
479 !! FORCE routine Calculates Lennard Jones forces.
480 !------------------------------------------------------------->
481 subroutine do_lj_ff(q,f,potE,do_pot)
482 real ( kind = dp ), dimension(ndim,) :: q
483 real ( kind = dp ), dimension(ndim,nLRparticles) :: f
484 real ( kind = dp ) :: potE
485 logical ( kind = 2) :: do_pot
486
487 type(lj_atype), pointer :: ljAtype_i
488 type(lj_atype), pointer :: ljAtype_j
489
490 #ifdef MPI
491 real( kind = DP ), dimension(3,ncol) :: efr
492 real( kind = DP ) :: pot_local
493 #else
494 ! real( kind = DP ), dimension(3,natoms) :: efr
495 #endif
496
497 real( kind = DP ) :: pe
498 logical, :: update_nlist
499
500
501 integer :: i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
502 integer :: nlist
503 integer :: j_start
504 integer :: tag_i,tag_j
505 real( kind = DP ) :: r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
506 real( kind = DP ) :: rxi, ryi, rzi, rxij, ryij, rzij, rijsq
507 real( kind = DP ) :: rlistsq, rcutsq
508
509 integer :: nrow
510 integer :: ncol
511
512 if (.not. isljFFInit) then
513 write(default_error,*) "ERROR: lj_FF has not been properly initialized"
514 return
515 endif
516
517 #ifndef IS_MPI
518 nrow = natoms - 1
519 ncol = natoms
520 #else
521 nrow = getNrow(plan_row)
522 ncol = getNcol(plan_col)
523 j_start = 1
524 #endif
525
526
527
528 call check(update_nlist)
529
530 !--------------WARNING...........................
531 ! Zero variables, NOTE:::: Forces are zeroed in C
532 ! Zeroing them here could delete previously computed
533 ! Forces.
534 !------------------------------------------------
535 #ifndef IS_MPI
536 nloops = nloops + 1
537 pot = 0.0E0_DP
538 e = 0.0E0_DP
539 #else
540 f_row = 0.0E0_DP
541 f_col = 0.0E0_DP
542
543 pot_local = 0.0E0_DP
544
545 e_row = 0.0E0_DP
546 e_col = 0.0E0_DP
547 e_tmp = 0.0E0_DP
548 #endif
549 efr = 0.0E0_DP
550
551 ! communicate MPI positions
552 #ifdef MPI
553 call gather(q,qRow,plan_row3)
554 call gather(q,qCol,plan_col3)
555 #endif
556
557 #ifndef MPI
558
559 #endif
560
561 if (update_nlist) then
562
563 ! save current configuration, contruct neighbor list,
564 ! and calculate forces
565 call save_nlist()
566
567 nlist = 0
568
569
570
571 do i = 1, nrow
572 point(i) = nlist + 1
573 #ifdef MPI
574 ljAtype_i => identPtrListRow(i)%this
575 tag_i = tagRow(i)
576 rxi = qRow(1,i)
577 ryi = qRow(2,i)
578 rzi = qRow(3,i)
579 #else
580 ljAtype_i => identPtrList(i)%this
581 j_start = i + 1
582 rxi = q(1,i)
583 ryi = q(2,i)
584 rzi = q(3,i)
585 #endif
586
587 inner: do j = j_start, ncol
588 #ifdef MPI
589 ! Assign identity pointers and tags
590 ljAtype_j => identPtrListColumn(j)%this
591 tag_j = tagCol(j)
592 if (newtons_thrd) then
593 if (tag_i <= tag_j) then
594 if (mod(tag_i + tag_j,2) == 0) cycle inner
595 else
596 if (mod(tag_i + tag_j,2) == 1) cycle inner
597 endif
598 endif
599
600 rxij = wrap(rxi - qCol(1,j), 1)
601 ryij = wrap(ryi - qCol(2,j), 2)
602 rzij = wrap(rzi - qCol(3,j), 3)
603 #else
604 ljAtype_j => identPtrList(j)%this
605 rxij = wrap(rxi - q(1,j), 1)
606 ryij = wrap(ryi - q(2,j), 2)
607 rzij = wrap(rzi - q(3,j), 3)
608
609 #endif
610 rijsq = rxij*rxij + ryij*ryij + rzij*rzij
611
612 #ifdef MPI
613 if (rijsq <= rlstsq .AND. &
614 tag_j /= tag_i) then
615 #else
616 if (rijsq < rlstsq) then
617 #endif
618
619 nlist = nlist + 1
620 if (nlist > size(list)) then
621 #warning "Change how nlist size is done"
622 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
623 endif
624 list(nlist) = j
625
626
627 if (rijsq < rcutsq) then
628
629 r = dsqrt(rijsq)
630
631 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
632
633 #ifdef MPI
634 e_row(i) = e_row(i) + pot*0.5
635 e_col(i) = e_col(i) + pot*0.5
636 #else
637 pe = pe + pot
638 #endif
639
640 efr(1,j) = -rxij
641 efr(2,j) = -ryij
642 efr(3,j) = -rzij
643
644 do dim = 1, 3
645
646
647 drdx1 = efr(dim,j) / r
648 ftmp = dudr * drdx1
649
650
651 #ifdef MPI
652 fCol(dim,j) = fCol(dim,j) - ftmp
653 fRow(dim,i) = fRow(dim,i) + ftmp
654 #else
655
656 f(dim,j) = f(dim,j) - ftmp
657 f(dim,i) = f(dim,i) + ftmp
658
659 #endif
660 enddo
661 endif
662 endif
663 enddo inner
664 enddo
665
666 #ifdef MPI
667 point(nrow + 1) = nlist + 1
668 #else
669 point(natoms) = nlist + 1
670 #endif
671
672 else
673
674 ! use the list to find the neighbors
675 do i = 1, nrow
676 JBEG = POINT(i)
677 JEND = POINT(i+1) - 1
678 ! check thiat molecule i has neighbors
679 if (jbeg .le. jend) then
680 #ifdef MPI
681 ljAtype_i => identPtrListRow(i)%this
682 rxi = qRow(1,i)
683 ryi = qRow(2,i)
684 rzi = qRow(3,i)
685 #else
686 ljAtype_i => identPtrList(i)%this
687 rxi = q(1,i)
688 ryi = q(2,i)
689 rzi = q(3,i)
690 #endif
691 do jnab = jbeg, jend
692 j = list(jnab)
693 #ifdef MPI
694 ljAtype_j = identPtrListColumn(j)%this
695 rxij = wrap(rxi - q_col(1,j), 1)
696 ryij = wrap(ryi - q_col(2,j), 2)
697 rzij = wrap(rzi - q_col(3,j), 3)
698 #else
699 ljAtype_j = identPtrList(j)%this
700 rxij = wrap(rxi - q(1,j), 1)
701 ryij = wrap(ryi - q(2,j), 2)
702 rzij = wrap(rzi - q(3,j), 3)
703 #endif
704 rijsq = rxij*rxij + ryij*ryij + rzij*rzij
705
706 if (rijsq < rcutsq) then
707
708 r = dsqrt(rijsq)
709
710 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
711 #ifdef MPI
712 e_row(i) = e_row(i) + pot*0.5
713 e_col(i) = e_col(i) + pot*0.5
714 #else
715 if (do_pot) pe = pe + pot
716 #endif
717
718
719 efr(1,j) = -rxij
720 efr(2,j) = -ryij
721 efr(3,j) = -rzij
722
723 do dim = 1, 3
724
725 drdx1 = efr(dim,j) / r
726 ftmp = dudr * drdx1
727 #ifdef MPI
728 fCol(dim,j) = fCol(dim,j) - ftmp
729 fRow(dim,i) = fRow(dim,i) + ftmp
730 #else
731 f(dim,j) = f(dim,j) - ftmp
732 f(dim,i) = f(dim,i) + ftmp
733 #endif
734 enddo
735 endif
736 enddo
737 endif
738 enddo
739 endif
740
741
742
743 #ifdef MPI
744 !!distribute forces
745 call scatter(fRow,f,plan_row3)
746
747 call scatter(fCol,f_tmp,plan_col3)
748 do i = 1,nlocal
749 do dim = 1,3
750 f(dim,i) = f(dim,i) + f_tmp(dim,i)
751 end do
752 end do
753
754
755
756 if (do_pot) then
757 ! scatter/gather pot_row into the members of my column
758 call scatter(e_row,e_tmp,plan_row)
759
760 ! scatter/gather pot_local into all other procs
761 ! add resultant to get total pot
762 do i = 1, nlocal
763 pot_local = pot_local + e_tmp(i)
764 enddo
765 if (newtons_thrd) then
766 e_tmp = 0.0E0_DP
767 call scatter(e_col,e_tmp,plan_col)
768 do i = 1, nlocal
769 pot_local = pot_local + e_tmp(i)
770 enddo
771 endif
772 endif
773 #endif
774
775
776
777
778 end subroutine do_lj_ff
779
780 !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
781 !! derivatives.
782 subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
783 ! arguments
784 !! Length of vector between particles
785 real( kind = dp ), intent(in) :: r
786 !! Potential Energy
787 real( kind = dp ), intent(out) :: pot
788 !! Derivatve wrt postion
789 real( kind = dp ), intent(out) :: dudr
790 !! Second Derivative, optional, used mainly for normal mode calculations.
791 real( kind = dp ), intent(out), optional :: d2
792
793 type (lj_atype), intent(in), pointer :: atype1
794 type (lj_atype), intent(in), pointer :: atype2
795
796 integer, intent(out), optional :: status
797
798 ! local Variables
799 real( kind = dp ) :: sigma
800 real( kind = dp ) :: sigma2
801 real( kind = dp ) :: sigma6
802 real( kind = dp ) :: epslon
803
804 real( kind = dp ) :: rcut
805 real( kind = dp ) :: rcut2
806 real( kind = dp ) :: rcut6
807 real( kind = dp ) :: r2
808 real( kind = dp ) :: r6
809
810 real( kind = dp ) :: t6
811 real( kind = dp ) :: t12
812 real( kind = dp ) :: tp6
813 real( kind = dp ) :: tp12
814 real( kind = dp ) :: delta
815
816 logical :: doSec = .false.
817
818 integer :: errorStat
819
820 !! Optional Argument Checking
821 ! Check to see if we need to do second derivatives
822
823 if (present(d2)) doSec = .true.
824 if (present(status)) status = 0
825
826 ! Look up the correct parameters in the mixing matrix
827 sigma = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
828 sigma2 = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
829 sigma6 = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
830 epslon = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
831
832
833
834 call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
835
836 r2 = r * r
837 r6 = r2 * r2 * r2
838
839 t6 = sigma6/ r6
840 t12 = t6 * t6
841
842
843
844 tp6 = sigma6 / rcut6
845 tp12 = tp6*tp6
846
847 delta = -4.0E0_DP*epsilon * (tp12 - tp6)
848
849 if (r.le.rcut) then
850 u = 4.0E0_DP * epsilon * (t12 - t6) + delta
851 dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
852 if(doSec) d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
853 else
854 u = 0.0E0_DP
855 dudr = 0.0E0_DP
856 if(doSec) d2 = 0.0E0_DP
857 endif
858
859 return
860
861
862
863 end subroutine getLjPot
864
865
866 !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
867 function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
868 character(len=*) :: thisParam
869 real(kind = dp) :: param1
870 real(kind = dp) :: param2
871 real(kind = dp ) :: myMixParam
872 integer, optional :: status
873
874
875 myMixParam = 0.0_dp
876
877 if (present(status)) status = 0
878
879 select case (thisParam)
880
881 case ("sigma")
882 myMixParam = 0.5_dp * (param1 + param2)
883 case ("epslon")
884 myMixParam = sqrt(param1 * param2)
885 case default
886 status = -1
887 end select
888
889 end function calcLJMix
890
891
892
893 end module lj_ff