ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90 (file contents):
Revision 329 by gezelter, Wed Mar 12 22:27:59 2003 UTC vs.
Revision 330 by gezelter, Wed Mar 12 23:15: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.15 2003-03-12 22:27:59 gezelter Exp $, $Date: 2003-03-12 22:27:59 $, $Name: not supported by cvs2svn $, $Revision: 1.15 $
7 > !! @version $Id: do_Forces.F90,v 1.16 2003-03-12 23:15:46 gezelter Exp $, $Date: 2003-03-12 23:15:46 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
8  
9  
10  
# Line 13 | Line 13 | module do_Forces
13    use definitions
14    use atype_module
15    use neighborLists  
16 <  use lj_FF
17 <  use sticky_FF
16 >  use lj
17 >  use sticky_pair
18    use dipole_dipole
19  use gb_FF
19  
20   #ifdef IS_MPI
21    use mpiSimulation
# Line 34 | Line 33 | module do_Forces
33  
34  
35    public :: init_FF
36 <  public :: do_forces
36 >  public :: do_force_loop
37  
38   contains
39  
# Line 86 | Line 85 | contains
85      logical :: do_stress
86   #ifdef IS_MPI
87      real( kind = DP ) :: pot_local
89    integer :: nlocal
88      integer :: nrow
89      integer :: ncol
90   #endif
91 +    integer :: nlocal
92      integer :: natoms    
93      logical :: update_nlist  
94      integer :: i, j, jbeg, jend, jnab
95      integer :: nlist
96      real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
97 +    real(kind=dp),dimension(3) :: d
98 +    real(kind=dp) :: rfpot, mu_i, virial
99 +    integer :: me_i
100 +    logical :: is_dp_i
101      integer :: neighborListSize
102 <    integer :: listerror
102 >    integer :: listerror, error
103  
104      !! initialize local variables  
105  
# Line 163 | Line 166 | contains
166            
167            inner: do j = 1, ncol
168              
169 <             if (check_exclude(i,j)) cycle inner:
169 >             if (checkExcludes(i,j)) cycle inner:
170              
171               call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
172 <            
172 >            
173               if (rijsq <  rlistsq) then            
174                  
175                  nlist = nlist + 1
# Line 227 | Line 230 | contains
230            
231            inner: do j = i+1, natoms
232              
233 <             if (check_exclude(i,j)) cycle inner:
233 >             if (checkExcludes(i,j)) cycle inner:
234              
235               call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
236            
# Line 258 | Line 261 | contains
261      else !! (update)
262        
263         ! use the list to find the neighbors
264 <       do i = 1, nrow
264 >       do i = 1, natoms-1
265            JBEG = POINT(i)
266            JEND = POINT(i+1) - 1
267            ! check thiat molecule i has neighbors
# Line 314 | Line 317 | contains
317            pot_local = pot_local + pot_Temp(i)
318         enddo
319        
320 <    endif
321 <    
320 >    endif    
321 > #endif
322 >
323      if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
324        
325         if (FF_uses_RF .and. SimUsesRF()) then
# Line 330 | Line 334 | contains
334            
335            do i = 1, getNlocal()
336  
337 +             rfpot = 0.0_DP
338   #ifdef IS_MPI
339               me_i = atid_row(i)
340   #else
# Line 343 | Line 348 | contains
348                  call accumulate_self_rf(i, mu_i, u_l)            
349                  !! Get the reaction field contribution to the
350                  !! potential and torques:
351 <                call reaction_field(i, mu_i, u_l, rfpot, t, do_pot)
351 >                call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
352   #ifdef IS_MPI
353                  pot_local = pot_local + rfpot
354   #else
# Line 364 | Line 369 | contains
369      endif
370  
371      if (do_stress) then
372 <       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
372 >       call mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
373              mpi_comm_world,mpi_err)
374 <       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
374 >       call mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
375              mpi_comm_world,mpi_err)
376      endif
377  
# Line 390 | Line 395 | contains
395  
396    end subroutine do_preForce
397  
398 < !! Calculate any post force loop components, i.e. reaction field, etc.
398 >  !! Calculate any post force loop components, i.e. reaction field, etc.
399    subroutine do_postForce()
400  
401  
# Line 399 | Line 404 | contains
404  
405    subroutine do_pair(i, j, rijsq, d, do_pot, do_stress)
406  
407 +    real( kind = dp ) :: pot
408 +    real( kind = dp ), dimension(3,getNlocal()) :: u_l
409 +    real (kind=dp), dimension(9,getNlocal()) :: A
410 +    real (kind=dp), dimension(3,getNlocal()) :: f
411 +    real (kind=dp), dimension(3,getNlocal()) :: t
412 +
413      logical, intent(inout) :: do_pot, do_stress
414      integer, intent(in) :: i, j
415      real ( kind = dp ), intent(in)    :: rijsq
416      real ( kind = dp )                :: r
417      real ( kind = dp ), intent(inout) :: d(3)
407
408    r = sqrt(rijsq)
409    
418      logical :: is_LJ_i, is_LJ_j
419      logical :: is_DP_i, is_DP_j
420      logical :: is_Sticky_i, is_Sticky_j
421      integer :: me_i, me_j
422  
423 +    r = sqrt(rijsq)
424 +    
425   #ifdef IS_MPI
426  
427      me_i = atid_row(i)
# Line 434 | Line 444 | contains
444      endif
445        
446  
447 <    if (FF_uses_DP .and. SimUsesDP()) then
447 >    if (FF_uses_dipoles .and. SimUsesDipoles()) then
448         call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
449         call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
450        
# Line 476 | Line 486 | contains
486      d(1:3) = q_i(1:3) - q_j(1:3)
487      
488      ! Wrap back into periodic box if necessary
489 <    if ( isPBC() ) then
490 <       d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
491 <            int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
489 >    if ( SimUsesPBC() ) then
490 >       d(1:3) = d(1:3) - box(1:3) * sign(1.0_dp,box(1:3)) * &
491 >            int(abs(d(1:3)/box(1:3) + 0.5_dp))
492      endif
493      
494      r_sq = dot_product(d,d)
# Line 540 | Line 550 | contains
550    end subroutine zero_work_arrays
551    
552  
553 < !! Function to properly build neighbor lists in MPI using newtons 3rd law.
554 < !! We don't want 2 processors doing the same i j pair twice.
555 < !! Also checks to see if i and j are the same particle.
553 >  !! Function to properly build neighbor lists in MPI using newtons 3rd law.
554 >  !! We don't want 2 processors doing the same i j pair twice.
555 >  !! Also checks to see if i and j are the same particle.
556 >
557    function checkExcludes(atom1,atom2) result(do_cycle)
558 < !--------------- Arguments--------------------------
559 < ! Index i
558 >    !--------------- Arguments--------------------------
559 >    ! Index i
560      integer,intent(in) :: atom1
561 < ! Index j
561 >    ! Index j
562      integer,intent(in), optional :: atom2
563 < ! Result do_cycle
563 >    ! Result do_cycle
564      logical :: do_cycle
565 < !--------------- Local variables--------------------
565 >    !--------------- Local variables--------------------
566      integer :: tag_i
567      integer :: tag_j
568 <    integer :: i
569 < !--------------- END DECLARATIONS------------------  
568 >    integer :: i, j
569 >    !--------------- END DECLARATIONS------------------  
570      do_cycle = .false.
571 <
571 >    
572   #ifdef IS_MPI
573      tag_i = tagRow(atom1)
574   #else
575      tag_i = tag(atom1)
576   #endif
577 <
578 < !! Check global excludes first
577 >    
578 >    !! Check global excludes first
579      if (.not. present(atom2)) then
580 <       do i = 1,nGlobalExcludes
580 >       do i = 1, nExcludes_global
581            if (excludeGlobal(i) == tag_i) then
582               do_cycle = .true.
583               return
# Line 575 | Line 586 | contains
586         return !! return after checking globals
587      end if
588  
589 < !! we return if j not present here.
590 <    tag_j = tagColumn(j)
591 <
581 <
582 <
589 >    !! we return if atom2 not present here.
590 >    tag_j = tagColumn(atom2)
591 >    
592      if (tag_i == tag_j) then
593         do_cycle = .true.
594         return
595      end if
596 <
596 >    
597      if (tag_i < tag_j) then
598         if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
599         return
600      else                
601         if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
602      endif
603 <
604 <
605 <
597 <    do i = 1, nLocalExcludes
598 <       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
603 >            
604 >    do i = 1, nExcludes_local
605 >       if ((tag_i == excludesLocal(1,i)) .and. (excludesLocal(2,i) < 0)) then
606            do_cycle = .true.
607            return
608         end if
609      end do
610 <      
611 <
610 >    
611 >    
612    end function checkExcludes
613  
614    function FF_UsesDirectionalAtoms() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines