ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/lj_FF.F90
(Generate patch)

Comparing trunk/mdtools/md_code/lj_FF.F90 (file contents):
Revision 215 by chuckv, Thu Dec 19 21:59:51 2002 UTC vs.
Revision 239 by chuckv, Mon Jan 20 22:36:12 2003 UTC

# Line 1 | Line 1
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.8 2003-01-20 22:36:12 chuckv Exp $, $Date: 2003-01-20 22:36:12 $, $Name: not supported by cvs2svn $, $Revision: 1.8 $
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 <     character(len = 15) :: name = "NULL"
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(name,mass,epslon,sigma,status)
26 <    character( len = 15 ) :: name
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) :: sigam
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 +
508 +  integer :: nrow
509 +  integer :: ncol
510 +
511 +  if (.not. isljFFInit) then
512 +     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
513 +     return
514 +  endif
515 +
516 + #ifndef IS_MPI
517 +  nrow = natoms - 1
518 +  ncol = natoms
519 + #else
520 +  nrow = getNrow(plan_row)
521 +  ncol = getNcol(plan_col)
522 +  j_start = 1
523 + #endif
524 +
525 +  
526 +
527 +  call check(update_nlist)
528 +
529 + !--------------WARNING...........................
530 + ! Zero variables, NOTE:::: Forces are zeroed in C
531 + ! Zeroing them here could delete previously computed
532 + ! Forces.
533 + !------------------------------------------------
534 + #ifndef IS_MPI
535 +  nloops = nloops + 1
536 +  pot = 0.0E0_DP
537 +  e = 0.0E0_DP
538 + #else
539 +    f_row = 0.0E0_DP
540 +    f_col = 0.0E0_DP
541 +
542 +    pot_local = 0.0E0_DP
543 +
544 +    e_row = 0.0E0_DP
545 +    e_col = 0.0E0_DP
546 +    e_tmp = 0.0E0_DP
547 + #endif
548 +    efr = 0.0E0_DP
549 +
550 + ! communicate MPI positions
551 + #ifdef MPI    
552 +    call gather(q,qRow,plan_row3)
553 +    call gather(q,qCol,plan_col3)
554 + #endif
555 +
556 + #ifndef MPI
557 +
558 + #endif
559 +
560 +  if (update_nlist) then
561 +
562 +     ! save current configuration, contruct neighbor list,
563 +     ! and calculate forces
564 +     call save_nlist()
565 +    
566 +     nlist = 0
567 +    
568 +    
569 +
570 +     do i = 1, nrow
571 +        point(i) = nlist + 1
572 + #ifdef MPI
573 +        ljAtype_i => identPtrListRow(i)%this
574 +        tag_i = tagRow(i)
575 +        rxi = qRow(1,i)
576 +        ryi = qRow(2,i)
577 +        rzi = qRow(3,i)
578 + #else
579 +        ljAtype_i   => identPtrList(i)%this
580 +        j_start = i + 1
581 +        rxi = q(1,i)
582 +        ryi = q(2,i)
583 +        rzi = q(3,i)
584 + #endif
585 +
586 +        inner: do j = j_start, ncol
587 + #ifdef MPI
588 + ! Assign identity pointers and tags
589 +           ljAtype_j => identPtrListColumn(j)%this
590 +           tag_j = tagCol(j)
591 +           if (newtons_thrd) then
592 +              if (tag_i <= tag_j) then
593 +                 if (mod(tag_i + tag_j,2) == 0) cycle inner
594 +              else                
595 +                 if (mod(tag_i + tag_j,2) == 1) cycle inner
596 +              endif
597 +           endif
598 +
599 +           rxij = wrap(rxi - qCol(1,j), 1)
600 +           ryij = wrap(ryi - qCol(2,j), 2)
601 +           rzij = wrap(rzi - qCol(3,j), 3)
602 + #else          
603 +           ljAtype_j   => identPtrList(j)%this
604 +           rxij = wrap(rxi - q(1,j), 1)
605 +           ryij = wrap(ryi - q(2,j), 2)
606 +           rzij = wrap(rzi - q(3,j), 3)
607 +      
608 + #endif          
609 +           rijsq = rxij*rxij + ryij*ryij + rzij*rzij
610 +
611 + #ifdef MPI
612 +             if (rijsq <=  rlstsq .AND. &
613 +                  tag_j /= tag_i) then
614 + #else
615 +             if (rijsq <  rlstsq) then
616 + #endif
617 +            
618 +              nlist = nlist + 1
619 +              if (nlist > size(list)) then
620 + #warning "Change how nlist size is done"
621 +                 write(DEFAULT_ERROR,*) "ERROR: nlist > list size"
622 +              endif
623 +              list(nlist) = j
624 +
625 +              
626 +              if (rijsq <  rcutsq) then
627 +                
628 +                 r = dsqrt(rijsq)
629 +      
630 +                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
631 +      
632 + #ifdef MPI
633 +                e_row(i) = e_row(i) + pot*0.5
634 +                e_col(i) = e_col(i) + pot*0.5
635 + #else
636 +                pe = pe + pot
637 + #endif                
638 +            
639 +                 efr(1,j) = -rxij
640 +                 efr(2,j) = -ryij
641 +                 efr(3,j) = -rzij
642 +
643 +                 do dim = 1, 3  
644 +
645 +            
646 +                    drdx1 = efr(dim,j) / r
647 +                    ftmp = dudr * drdx1
648 +
649 +
650 + #ifdef MPI
651 +                    fCol(dim,j) = fCol(dim,j) - ftmp
652 +                    fRow(dim,i) = fRow(dim,i) + ftmp
653 + #else                    
654 +            
655 +                    f(dim,j) = f(dim,j) - ftmp
656 +                    f(dim,i) = f(dim,i) + ftmp
657 +
658 + #endif                    
659 +                 enddo
660 +              endif
661 +           endif
662 +        enddo inner
663 +     enddo
664 +
665 + #ifdef MPI
666 +     point(nrow + 1) = nlist + 1
667 + #else
668 +     point(natoms) = nlist + 1
669 + #endif
670 +
671 +  else
672 +
673 +     ! use the list to find the neighbors
674 +     do i = 1, nrow
675 +        JBEG = POINT(i)
676 +        JEND = POINT(i+1) - 1
677 +        ! check thiat molecule i has neighbors
678 +        if (jbeg .le. jend) then
679 + #ifdef MPI
680 +           ljAtype_i => identPtrListRow(i)%this
681 +           rxi = qRow(1,i)
682 +           ryi = qRow(2,i)
683 +           rzi = qRow(3,i)
684 + #else
685 +           ljAtype_i   => identPtrList(i)%this
686 +           rxi = q(1,i)
687 +           ryi = q(2,i)
688 +           rzi = q(3,i)
689 + #endif
690 +           do jnab = jbeg, jend
691 +              j = list(jnab)
692 + #ifdef MPI
693 +              ljAtype_j = identPtrListColumn(j)%this
694 +              rxij = wrap(rxi - q_col(1,j), 1)
695 +              ryij = wrap(ryi - q_col(2,j), 2)
696 +              rzij = wrap(rzi - q_col(3,j), 3)
697 + #else
698 +              ljAtype_j = identPtrList(j)%this
699 +              rxij = wrap(rxi - q(1,j), 1)
700 +              ryij = wrap(ryi - q(2,j), 2)
701 +              rzij = wrap(rzi - q(3,j), 3)
702 + #endif
703 +              rijsq = rxij*rxij + ryij*ryij + rzij*rzij
704 +              
705 +              if (rijsq <  rcutsq) then
706 +
707 +                 r = dsqrt(rijsq)
708 +                
709 +                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
710 + #ifdef MPI
711 +                e_row(i) = e_row(i) + pot*0.5
712 +                e_col(i) = e_col(i) + pot*0.5
713 + #else
714 +               if (do_pot)  pe = pe + pot
715 + #endif                
716 +
717 +                
718 +                 efr(1,j) = -rxij
719 +                 efr(2,j) = -ryij
720 +                 efr(3,j) = -rzij
721 +
722 +                 do dim = 1, 3                        
723 +                    
724 +                    drdx1 = efr(dim,j) / r
725 +                    ftmp = dudr * drdx1
726 + #ifdef MPI
727 +                    fCol(dim,j) = fCol(dim,j) - ftmp
728 +                    fRow(dim,i) = fRow(dim,i) + ftmp
729 + #else                    
730 +                    f(dim,j) = f(dim,j) - ftmp
731 +                    f(dim,i) = f(dim,i) + ftmp
732 + #endif                    
733 +                 enddo
734 +              endif
735 +           enddo
736 +        endif
737 +     enddo
738 +  endif
739 +
740 +
741 +
742 + #ifdef MPI
743 +    !!distribute forces
744 +    call scatter(fRow,f,plan_row3)
745 +
746 +    call scatter(fCol,f_tmp,plan_col3)
747 +    do i = 1,nlocal
748 +       do dim = 1,3
749 +          f(dim,i) = f(dim,i) + f_tmp(dim,i)
750 +       end do
751 +    end do
752 +
753 +
754 +    
755 +    if (do_pot) then
756 + ! scatter/gather pot_row into the members of my column
757 +       call scatter(e_row,e_tmp,plan_row)
758 +      
759 +       ! scatter/gather pot_local into all other procs
760 +       ! add resultant to get total pot
761 +       do i = 1, nlocal
762 +          pot_local = pot_local + e_tmp(i)
763 +       enddo
764 +       if (newtons_thrd) then
765 +          e_tmp = 0.0E0_DP
766 +          call scatter(e_col,e_tmp,plan_col)
767 +          do i = 1, nlocal
768 +             pot_local = pot_local + e_tmp(i)
769 +          enddo
770 +       endif
771 +    endif
772 + #endif
773 +
774 +
775 +
776 +
777 +  end subroutine do_lj_ff
778 +
779 + !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
780 + !! derivatives.
781 +  subroutine getLjPot(r,pot,dudr,atype1,atype2,d2,status)
782 + ! arguments
783 + !! Length of vector between particles
784 +    real( kind = dp ), intent(in)  :: r
785 + !! Potential Energy
786 +    real( kind = dp ), intent(out) :: pot
787 + !! Derivatve wrt postion
788 +    real( kind = dp ), intent(out) :: dudr
789 + !! Second Derivative, optional, used mainly for normal mode calculations.
790 +    real( kind = dp ), intent(out), optional :: d2
791 +    
792 +    type (lj_atype), intent(in), pointer :: atype1
793 +    type (lj_atype), intent(in), pointer :: atype2
794 +
795 +    integer, intent(out), optional :: status
796 +
797 + ! local Variables
798 +    real( kind = dp ) :: sigma
799 +    real( kind = dp ) :: sigma2
800 +    real( kind = dp ) :: sigma6
801 +    real( kind = dp ) :: epslon
802 +
803 +    real( kind = dp ) :: rcut
804 +    real( kind = dp ) :: rcut2
805 +    real( kind = dp ) :: rcut6
806 +    real( kind = dp ) :: r2
807 +    real( kind = dp ) :: r6
808 +
809 +    real( kind = dp ) :: t6
810 +    real( kind = dp ) :: t12
811 +    real( kind = dp ) :: tp6
812 +    real( kind = dp ) :: tp12
813 +    real( kind = dp ) :: delta
814 +
815 +    logical :: doSec = .false.
816 +
817 +    integer :: errorStat
818 +
819 + !! Optional Argument Checking
820 + ! Check to see if we need to do second derivatives
821 +    
822 +    if (present(d2))     doSec = .true.
823 +    if (present(status)) status = 0
824 +
825 + ! Look up the correct parameters in the mixing matrix
826 +    sigma   = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma
827 +    sigma2  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma2
828 +    sigma6  = ljMixed(atype1%atype_ident,atype2_atype_ident)%sigma6
829 +    epslon  = ljMixed(atype1%atype_ident,atype2_atype_ident)%epslon
830 +
831 +
832 +
833 +    call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
834 +    
835 +    r2 = r * r
836 +    r6 = r2 * r2 * r2
837 +
838 +    t6  = sigma6/ r6
839 +    t12 = t6 * t6
840 +
841 +
842 +                                                                              
843 +    tp6 = sigma6 / rcut6
844 +    tp12 = tp6*tp6
845 +                                                                              
846 +    delta = -4.0E0_DP*epsilon * (tp12 - tp6)
847 +                                                                              
848 +    if (r.le.rcut) then
849 +       u = 4.0E0_DP * epsilon * (t12 - t6) + delta
850 +       dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
851 +       if(doSec)  d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
852 +    else
853 +       u = 0.0E0_DP
854 +       dudr = 0.0E0_DP
855 +       if(doSec) d2 = 0.0E0_DP
856 +    endif
857 +                                                                              
858 +  return
859 +
860 +
861 +
862 +  end subroutine getLjPot
863 +
864 +
865 + !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
866 +  function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
867 +    character(len=*) :: thisParam
868 +    real(kind = dp)  :: param1
869 +    real(kind = dp)  :: param2
870 +    real(kind = dp ) :: myMixParam
871 +    integer, optional :: status
872 +
873 +
874 +    myMixParam = 0.0_dp
875 +
876 +    if (present(status)) status = 0
877 +
878 +    select case (thisParam)
879 +
880 +    case ("sigma")
881 +       myMixParam = 0.5_dp * (param1 + param2)
882 +    case ("epslon")
883 +       myMixParam = sqrt(param1 * param2)
884 +    case default
885 +       status = -1
886 +    end select
887 +
888 +  end function calcLJMix
889 +
890 +
891 +
892   end module lj_ff

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines