ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
(Generate patch)

Comparing:
branches/mmeineke/OOPSE/libmdtools/do_Forces.F90 (file contents), Revision 377 by mmeineke, Fri Mar 21 17:42:12 2003 UTC vs.
trunk/OOPSE/libmdtools/do_Forces.F90 (file contents), Revision 470 by chuckv, Mon Apr 7 20:50:46 2003 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.1.1.1 2003-03-21 17:42:12 mmeineke Exp $, $Date: 2003-03-21 17:42:12 $, $Name: not supported by cvs2svn $, $Revision: 1.1.1.1 $
7 > !! @version $Id: do_Forces.F90,v 1.11 2003-04-07 20:50:46 chuckv Exp $, $Date: 2003-04-07 20:50:46 $, $Name: not supported by cvs2svn $, $Revision: 1.11 $
8  
9   module do_Forces
10    use force_globals
# Line 167 | Line 167 | contains
167      logical ( kind = 2) :: do_pot_c, do_stress_c
168      logical :: do_pot
169      logical :: do_stress
170 < #ifdef IS_MPI
170 > #ifdef IS_MPI
171      real( kind = DP ) :: pot_local
172      integer :: nrow
173      integer :: ncol
# Line 189 | Line 189 | contains
189      !! initialize local variables  
190  
191   #ifdef IS_MPI
192 +    pot_local = 0.0_dp
193      nlocal = getNlocal()
194      nrow   = getNrow(plan_row)
195      ncol   = getNcol(plan_col)
# Line 196 | Line 197 | contains
197      nlocal = getNlocal()
198      natoms = nlocal
199   #endif
200 <
200 >  
201      call getRcut(rcut,rc2=rcutsq)
202      call getRlist(rlist,rlistsq)
203      
# Line 209 | Line 210 | contains
210  
211      do_pot = do_pot_c
212      do_stress = do_stress_c
213 +    
214  
215      ! Gather all information needed by all force loops:
216      
# Line 245 | Line 247 | contains
247        
248         !! save current configuration, construct neighbor list,
249         !! and calculate forces
250 <       call saveNeighborList(q)
250 >       call saveNeighborList(nlocal, q)
251        
252         neighborListSize = size(list)
253         nlist = 0      
# Line 277 | Line 279 | contains
279                                  
280                  if (rijsq <  rcutsq) then
281                     call do_pair(i, j, rijsq, d, do_pot, do_stress, &
282 <                        u_l, A, f, t,pot)
282 >                        u_l, A, f, t, pot_local)
283                  endif
284               endif
285            enddo inner
# Line 299 | Line 301 | contains
301  
302                  call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
303                  call do_pair(i, j, rijsq, d, do_pot, do_stress, &
304 <                     u_l, A, f, t,pot)
304 >                     u_l, A, f, t, pot_local)
305  
306               enddo
307            endif
# Line 312 | Line 314 | contains
314        
315         ! save current configuration, contruct neighbor list,
316         ! and calculate forces
317 <       call saveNeighborList(q)
317 >       call saveNeighborList(natoms, q)
318        
319         neighborListSize = size(list)
320    
# Line 323 | Line 325 | contains
325            
326            inner: do j = i+1, natoms
327              
328 <             if (skipThisPair(i,j)) cycle inner
329 <            
328 >             if (skipThisPair(i,j))  cycle inner
329 >                          
330               call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
331            
332 +
333               if (rijsq <  rlistsq) then
334                  
335                  nlist = nlist + 1
# Line 345 | Line 348 | contains
348                  
349                  if (rijsq <  rcutsq) then
350                     call do_pair(i, j, rijsq, d, do_pot, do_stress, &
351 <                        u_l, A, f, t,pot)
351 >                        u_l, A, f, t, pot)
352                  endif
353               endif
354            enddo inner
# Line 367 | Line 370 | contains
370  
371                  call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
372                  call do_pair(i, j, rijsq, d, do_pot, do_stress, &
373 <                     u_l, A, f, t,pot)
373 >                     u_l, A, f, t, pot)
374  
375               enddo
376            endif
# Line 380 | Line 383 | contains
383      
384   #ifdef IS_MPI
385      !!distribute forces
386 <    
387 <    call scatter(f_Row,f,plan_row3d)
386 >  
387 >    f_temp = 0.0_dp
388 >    call scatter(f_Row,f_temp,plan_row3d)
389 >    do i = 1,nlocal
390 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
391 >    end do
392 >
393 >    f_temp = 0.0_dp
394      call scatter(f_Col,f_temp,plan_col3d)
395      do i = 1,nlocal
396         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
397      end do
398      
399      if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
400 <       call scatter(t_Row,t,plan_row3d)
400 >       t_temp = 0.0_dp
401 >       call scatter(t_Row,t_temp,plan_row3d)
402 >       do i = 1,nlocal
403 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
404 >       end do
405 >       t_temp = 0.0_dp
406         call scatter(t_Col,t_temp,plan_col3d)
407        
408         do i = 1,nlocal
# Line 399 | Line 413 | contains
413      if (do_pot) then
414         ! scatter/gather pot_row into the members of my column
415         call scatter(pot_Row, pot_Temp, plan_row)
416 <      
416 >
417         ! scatter/gather pot_local into all other procs
418         ! add resultant to get total pot
419         do i = 1, nlocal
420            pot_local = pot_local + pot_Temp(i)
421         enddo
422 +      
423 +       pot_Temp = 0.0_DP
424  
409       pot_Temp = 0.0_DP
410
425         call scatter(pot_Col, pot_Temp, plan_col)
426         do i = 1, nlocal
427            pot_local = pot_local + pot_Temp(i)
428         enddo
429 <      
429 >
430      endif    
431   #endif
432  
# Line 460 | Line 474 | contains
474   #ifdef IS_MPI
475  
476      if (do_pot) then
477 <       pot = pot_local
477 >       pot = pot + pot_local
478         !! we assume the c code will do the allreduce to get the total potential
479         !! we could do it right here if we needed to...
480      endif
481  
482      if (do_stress) then
483 <       call mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
483 >       call mpi_allreduce(tau_Temp, tau,9,mpi_double_precision,mpi_sum, &
484              mpi_comm_world,mpi_err)
485 <       call mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
485 >       call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
486              mpi_comm_world,mpi_err)
487      endif
488  
# Line 483 | Line 497 | contains
497      
498    end subroutine do_force_loop
499  
500 <  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t,pot)
500 >  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
501  
502      real( kind = dp ) :: pot
503 <    real( kind = dp ), dimension(:,:) :: u_l
504 <    real (kind=dp), dimension(:,:) :: A
505 <    real (kind=dp), dimension(:,:) :: f
506 <    real (kind=dp), dimension(:,:) :: t
503 >    real( kind = dp ), dimension(3,getNlocal()) :: u_l
504 >    real (kind=dp), dimension(9,getNlocal()) :: A
505 >    real (kind=dp), dimension(3,getNlocal()) :: f
506 >    real (kind=dp), dimension(3,getNlocal()) :: t
507  
508      logical, intent(inout) :: do_pot, do_stress
509      integer, intent(in) :: i, j
# Line 532 | Line 546 | contains
546            
547            call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
548                 do_pot, do_stress)
535          
549            if (FF_uses_RF .and. SimUsesRF()) then
537            
550               call accumulate_rf(i, j, r, u_l)
551               call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
540            
552            endif
553            
554         endif
# Line 547 | Line 558 | contains
558  
559         call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
560         call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
561 <      
561 >
562         if ( is_Sticky_i .and. is_Sticky_j ) then
563            call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
564                 do_pot, do_stress)
# Line 580 | Line 591 | contains
591      d_old = d
592      ! Wrap back into periodic box if necessary
593      if ( SimUsesPBC() ) then
594 <
594 >      
595         d(1:3) = d(1:3) - box(1:3) * sign(1.0_dp,d(1:3)) * &
596              int(abs(d(1:3)/box(1:3)) + 0.5_dp)
597 <
597 >      
598      endif
599      r_sq = dot_product(d,d)
600          
# Line 645 | Line 656 | contains
656      rf = 0.0_dp
657      tau_Temp = 0.0_dp
658      virial_Temp = 0.0_dp
648    
659    end subroutine zero_work_arrays
660    
661    function skipThisPair(atom1, atom2) result(skip_it)
652    
662      integer, intent(in) :: atom1
663      integer, intent(in), optional :: atom2
664      logical :: skip_it
665      integer :: unique_id_1, unique_id_2
666 +    integer :: me_i,me_j
667      integer :: i
668  
669      skip_it = .false.
# Line 671 | Line 681 | contains
681      !! in the normal loop, the atom numbers are unique
682      unique_id_1 = atom1
683   #endif
684 <    
684 >
685      !! We were called with only one atom, so just check the global exclude
686      !! list for this atom
687      if (.not. present(atom2)) then
# Line 689 | Line 699 | contains
699   #else
700      unique_id_2 = atom2
701   #endif
702 <    
702 >
703   #ifdef IS_MPI
704      !! this situation should only arise in MPI simulations
705      if (unique_id_1 == unique_id_2) then
# Line 699 | Line 709 | contains
709      
710      !! this prevents us from doing the pair on multiple processors
711      if (unique_id_1 < unique_id_2) then
712 <       if (mod(unique_id_1 + unique_id_2,2) == 0) skip_it = .true.
713 <       return
712 >       if (mod(unique_id_1 + unique_id_2,2) == 0) then
713 >          skip_it = .true.
714 >          return
715 >       endif
716      else                
717 <       if (mod(unique_id_1 + unique_id_2,2) == 1) skip_it = .true.
718 <       return
717 >       if (mod(unique_id_1 + unique_id_2,2) == 1) then
718 >          skip_it = .true.
719 >          return
720 >       endif
721      endif
722   #endif
723 <
723 >
724      !! the rest of these situations can happen in all simulations:
725      do i = 1, nExcludes_global      
726         if ((excludesGlobal(i) == unique_id_1) .or. &
# Line 715 | Line 729 | contains
729            return
730         endif
731      enddo
732 <  
732 >
733      do i = 1, nExcludes_local
734         if (excludesLocal(1,i) == unique_id_1) then
735            if (excludesLocal(2,i) == unique_id_2) then

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines