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 332 by gezelter, Thu Mar 13 15:28:43 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.18 2003-03-13 15:28:43 gezelter Exp $, $Date: 2003-03-13 15:28:43 $, $Name: not supported by cvs2svn $, $Revision: 1.18 $
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 >  use reaction_field
20  
21   #ifdef IS_MPI
22    use mpiSimulation
# Line 32 | Line 32 | module do_Forces
32    logical, save :: FF_uses_GB
33    logical, save :: FF_uses_EAM
34  
35
35    public :: init_FF
36 <  public :: do_forces
36 >  public :: do_force_loop
37  
38   contains
39  
40 <  subroutine init_FF(thisStat)
41 <  
42 <    integer, intent(out) :: my_status
43 <    integer :: thisStat = 0
40 >  subroutine init_FF(LJ_mix_policy, use_RF_c, thisStat)
41 >    logical(kind = 2), intent(in) :: use_RF_c
42 >    logical :: use_RF_f
43 >    integer, intent(out) :: thisStat  
44 >    integer :: my_status, nMatches
45 >    character(len = 100) :: LJ_mix_Policy
46 >    integer, pointer :: MatchList(:)
47 >    
48 >    !! Fortran's version of a cast:
49 >    use_RF_f = use_RF_c
50  
51 <    ! be a smarter subroutine.
51 >    !! assume things are copacetic, unless they aren't
52 >    thisStat = 0
53 >    
54 >    !! init_FF is called *after* all of the atom types have been
55 >    !! defined in atype_module using the new_atype subroutine.
56 >    !!
57 >    !! this will scan through the known atypes and figure out what
58 >    !! interactions are used by the force field.    
59  
60 +    FF_uses_LJ = .false.
61 +    FF_uses_sticky = .false.
62 +    FF_uses_dipoles = .false.
63 +    FF_uses_GB = .false.
64 +    FF_uses_EAM = .false.
65      
66 <    call init_lj_FF(my_status)
66 >    call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
67 >    deallocate(MatchList)
68 >    if (nMatches .gt. 0) FF_uses_LJ = .true.
69 >
70 >    call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
71 >    deallocate(MatchList)
72 >    if (nMatches .gt. 0) FF_uses_dipoles = .true.
73 >
74 >    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
75 >         MatchList)
76 >    deallocate(MatchList)
77 >    if (nMatches .gt. 0) FF_uses_Sticky = .true.
78 >    
79 >    call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
80 >    deallocate(MatchList)
81 >    if (nMatches .gt. 0) FF_uses_GB = .true.
82 >
83 >    call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
84 >    deallocate(MatchList)
85 >    if (nMatches .gt. 0) FF_uses_EAM = .true.
86 >
87 >    !! check to make sure the use_RF setting makes sense
88 >    if (use_RF_f) then
89 >       if (FF_uses_dipoles) then
90 >          FF_uses_RF = .true.
91 >          call initialize_rf()
92 >       else
93 >          write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
94 >          thisStat = -1
95 >          return
96 >       endif
97 >    endif
98 >    
99 >    call init_lj_FF(LJ_mix_Policy, my_status)
100      if (my_status /= 0) then
101         thisStat = -1
102         return
# Line 86 | Line 136 | contains
136      logical :: do_stress
137   #ifdef IS_MPI
138      real( kind = DP ) :: pot_local
89    integer :: nlocal
139      integer :: nrow
140      integer :: ncol
141   #endif
142 +    integer :: nlocal
143      integer :: natoms    
144      logical :: update_nlist  
145      integer :: i, j, jbeg, jend, jnab
146      integer :: nlist
147      real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
148 +    real(kind=dp),dimension(3) :: d
149 +    real(kind=dp) :: rfpot, mu_i, virial
150 +    integer :: me_i
151 +    logical :: is_dp_i
152      integer :: neighborListSize
153 <    integer :: listerror
153 >    integer :: listerror, error
154 >    integer :: localError
155  
156      !! initialize local variables  
157  
# Line 109 | Line 164 | contains
164      natoms = nlocal
165   #endif
166  
167 <    call getRcut(rcut,rcut2=rcutsq)
167 >    call getRcut(rcut,rc2=rcutsq)
168      call getRlist(rlist,rlistsq)
169      
170 <    call check_initialization()
170 >    call check_initialization(localError)
171 >    if ( localError .ne. 0 ) then
172 >       error = -1
173 >       return
174 >    end if
175      call zero_work_arrays()
176  
177      do_pot = do_pot_c
# Line 163 | Line 222 | contains
222            
223            inner: do j = 1, ncol
224              
225 <             if (check_exclude(i,j)) cycle inner:
225 >             if (checkExcludes(i,j)) cycle inner
226              
227               call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
228 <            
228 >            
229               if (rijsq <  rlistsq) then            
230                  
231                  nlist = nlist + 1
# Line 227 | Line 286 | contains
286            
287            inner: do j = i+1, natoms
288              
289 <             if (check_exclude(i,j)) cycle inner:
289 >             if (checkExcludes(i,j)) cycle inner
290              
291               call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
292            
# Line 258 | Line 317 | contains
317      else !! (update)
318        
319         ! use the list to find the neighbors
320 <       do i = 1, nrow
320 >       do i = 1, natoms-1
321            JBEG = POINT(i)
322            JEND = POINT(i+1) - 1
323            ! check thiat molecule i has neighbors
# Line 314 | Line 373 | contains
373            pot_local = pot_local + pot_Temp(i)
374         enddo
375        
376 <    endif
377 <    
376 >    endif    
377 > #endif
378 >
379      if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
380        
381         if (FF_uses_RF .and. SimUsesRF()) then
# Line 330 | Line 390 | contains
390            
391            do i = 1, getNlocal()
392  
393 +             rfpot = 0.0_DP
394   #ifdef IS_MPI
395               me_i = atid_row(i)
396   #else
# Line 343 | Line 404 | contains
404                  call accumulate_self_rf(i, mu_i, u_l)            
405                  !! Get the reaction field contribution to the
406                  !! potential and torques:
407 <                call reaction_field(i, mu_i, u_l, rfpot, t, do_pot)
407 >                call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
408   #ifdef IS_MPI
409                  pot_local = pot_local + rfpot
410   #else
# Line 364 | Line 425 | contains
425      endif
426  
427      if (do_stress) then
428 <       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
428 >       call mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
429              mpi_comm_world,mpi_err)
430 <       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
430 >       call mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
431              mpi_comm_world,mpi_err)
432      endif
433  
# Line 381 | Line 442 | contains
442      
443    end subroutine do_force_loop
444  
384
385 !! Calculate any pre-force loop components and update nlist if necessary.
386  subroutine do_preForce(updateNlist)
387    logical, intent(inout) :: updateNlist
388
389
390
391  end subroutine do_preForce
392
393 !! Calculate any post force loop components, i.e. reaction field, etc.
394  subroutine do_postForce()
395
396
397
398  end subroutine do_postForce
399
445    subroutine do_pair(i, j, rijsq, d, do_pot, do_stress)
446  
447 +    real( kind = dp ) :: pot
448 +    real( kind = dp ), dimension(3,getNlocal()) :: u_l
449 +    real (kind=dp), dimension(9,getNlocal()) :: A
450 +    real (kind=dp), dimension(3,getNlocal()) :: f
451 +    real (kind=dp), dimension(3,getNlocal()) :: t
452 +
453      logical, intent(inout) :: do_pot, do_stress
454      integer, intent(in) :: i, j
455 <    real ( kind = dp ), intent(in)    :: rijsq
455 >    real ( kind = dp ), intent(inout)    :: rijsq
456      real ( kind = dp )                :: r
457      real ( kind = dp ), intent(inout) :: d(3)
407
408    r = sqrt(rijsq)
409    
458      logical :: is_LJ_i, is_LJ_j
459      logical :: is_DP_i, is_DP_j
460      logical :: is_Sticky_i, is_Sticky_j
461      integer :: me_i, me_j
462  
463 +    r = sqrt(rijsq)
464 +    
465   #ifdef IS_MPI
466  
467      me_i = atid_row(i)
# Line 434 | Line 484 | contains
484      endif
485        
486  
487 <    if (FF_uses_DP .and. SimUsesDP()) then
487 >    if (FF_uses_dipoles .and. SimUsesDipoles()) then
488         call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
489         call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
490        
# Line 476 | Line 526 | contains
526      d(1:3) = q_i(1:3) - q_j(1:3)
527      
528      ! Wrap back into periodic box if necessary
529 <    if ( isPBC() ) then
530 <       d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
531 <            int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
529 >    if ( SimUsesPBC() ) then
530 >       d(1:3) = d(1:3) - box(1:3) * sign(1.0_dp,box(1:3)) * &
531 >            int(abs(d(1:3)/box(1:3) + 0.5_dp))
532      endif
533      
534      r_sq = dot_product(d,d)
# Line 487 | Line 537 | contains
537  
538    subroutine check_initialization(error)
539      integer, intent(out) :: error
540 <
540 >    
541      error = 0
542      ! Make sure we are properly initialized.
543 <    if (.not. do_Forces_initialized) then
543 >    if (.not. do_forces_initialized) then
544         write(default_error,*) "ERROR: do_Forces has not been initialized!"
545         error = -1
546         return
547      endif
548 +
549   #ifdef IS_MPI
550      if (.not. isMPISimSet()) then
551         write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
# Line 502 | Line 553 | contains
553         return
554      endif
555   #endif
556 <
556 >    
557      return
558    end subroutine check_initialization
559  
# Line 532 | Line 583 | contains
583      pot_Col = 0.0_dp
584      pot_Temp = 0.0_dp
585  
586 +    rf_Row = 0.0_dp
587 +    rf_Col = 0.0_dp
588 +    rf_Temp = 0.0_dp
589 +
590   #endif
591  
592 +    rf = 0.0_dp
593      tau_Temp = 0.0_dp
594      virial_Temp = 0.0_dp
595      
596    end subroutine zero_work_arrays
597    
598  
599 < !! Function to properly build neighbor lists in MPI using newtons 3rd law.
600 < !! We don't want 2 processors doing the same i j pair twice.
601 < !! Also checks to see if i and j are the same particle.
599 >  !! Function to properly build neighbor lists in MPI using newtons 3rd law.
600 >  !! We don't want 2 processors doing the same i j pair twice.
601 >  !! Also checks to see if i and j are the same particle.
602 >
603    function checkExcludes(atom1,atom2) result(do_cycle)
604 < !--------------- Arguments--------------------------
548 < ! Index i
604 >    
605      integer,intent(in) :: atom1
550 ! Index j
606      integer,intent(in), optional :: atom2
552 ! Result do_cycle
607      logical :: do_cycle
608 < !--------------- Local variables--------------------
609 <    integer :: tag_i
556 <    integer :: tag_j
557 <    integer :: i
558 < !--------------- END DECLARATIONS------------------  
559 <    do_cycle = .false.
608 >    integer :: unique_id_1, unique_id_2
609 >    integer :: i, j
610  
611 +    do_cycle = .false.
612 +    
613   #ifdef IS_MPI
614 <    tag_i = tagRow(atom1)
614 >    unique_id_1 = tagRow(atom1)
615   #else
616 <    tag_i = tag(atom1)
616 >    unique_id_1 = tag(atom1)
617   #endif
618 <
619 < !! Check global excludes first
618 >    
619 >    !! Check global excludes first
620      if (.not. present(atom2)) then
621 <       do i = 1,nGlobalExcludes
622 <          if (excludeGlobal(i) == tag_i) then
621 >       do i = 1, nExcludes_global
622 >          if (excludesGlobal(i) == unique_id_1) then
623               do_cycle = .true.
624               return
625            end if
# Line 575 | Line 627 | contains
627         return !! return after checking globals
628      end if
629  
630 < !! we return if j not present here.
631 <    tag_j = tagColumn(j)
632 <
633 <
634 <
635 <    if (tag_i == tag_j) then
630 >    !! we return if atom2 not present here.
631 >    
632 > #ifdef IS_MPI
633 >    unique_id_2 = tagColumn(atom2)
634 > #else
635 >    unique_id_2 = tag(atom2)
636 > #endif
637 >    
638 >    if (unique_id_1 == unique_id_2) then
639         do_cycle = .true.
640         return
641      end if
642 <
643 <    if (tag_i < tag_j) then
644 <       if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
642 >    
643 >    if (unique_id_1 < unique_id_2) then
644 >       if (mod(unique_id_1 + unique_id_2,2) == 0) do_cycle = .true.
645         return
646      else                
647 <       if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
647 >       if (mod(unique_id_1 + unique_id_2,2) == 1) do_cycle = .true.
648      endif
649 <
650 <
651 <
652 <    do i = 1, nLocalExcludes
598 <       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
649 >    
650 >    do i = 1, nExcludes_local
651 >       if ((unique_id_1 == excludesLocal(1,i)) .and.  &
652 >            (excludesLocal(2,i) < 0)) then
653            do_cycle = .true.
654            return
655         end if
656      end do
657 <      
604 <
657 >    
658    end function checkExcludes
659  
660    function FF_UsesDirectionalAtoms() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines