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

Comparing trunk/OOPSE/libmdtools/do_Forces.F90 (file contents):
Revision 438 by chuckv, Mon Mar 31 21:50:59 2003 UTC vs.
Revision 631 by chuckv, Thu Jul 17 19:25:51 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.5 2003-03-31 21:50:59 chuckv Exp $, $Date: 2003-03-31 21:50:59 $, $Name: not supported by cvs2svn $, $Revision: 1.5 $
7 > !! @version $Id: do_Forces.F90,v 1.22 2003-07-17 19:25:51 chuckv Exp $, $Date: 2003-07-17 19:25:51 $, $Name: not supported by cvs2svn $, $Revision: 1.22 $
8  
9   module do_Forces
10    use force_globals
# Line 17 | Line 17 | module do_Forces
17    use dipole_dipole
18    use reaction_field
19    use gb_pair
20 +  use vector_class
21   #ifdef IS_MPI
22    use mpiSimulation
23   #endif
# Line 27 | Line 28 | module do_Forces
28   #define __FORTRAN90
29   #include "fForceField.h"
30  
31 <  logical, save :: do_forces_initialized = .false.
31 >  logical, save :: do_forces_initialized = .false., haveRlist = .false.
32 >  logical, save :: havePolicies = .false.
33    logical, save :: FF_uses_LJ
34    logical, save :: FF_uses_sticky
35    logical, save :: FF_uses_dipoles
# Line 35 | Line 37 | module do_Forces
37    logical, save :: FF_uses_GB
38    logical, save :: FF_uses_EAM
39  
40 +  real(kind=dp), save :: rlist, rlistsq
41 +
42    public :: init_FF
43    public :: do_force_loop
44 +  public :: setRlistDF
45  
46   contains
47  
48 +  subroutine setRlistDF( this_rlist )
49 +    
50 +    real(kind=dp) :: this_rlist
51 +
52 +    rlist = this_rlist
53 +    rlistsq = rlist * rlist
54 +    
55 +    haveRlist = .true.
56 +    if( havePolicies ) do_forces_initialized = .true.
57 +
58 +  end subroutine setRlistDF    
59 +
60    subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
61  
62      integer, intent(in) :: LJMIXPOLICY
# Line 87 | Line 104 | contains
104      !! check to make sure the FF_uses_RF setting makes sense
105      
106      if (FF_uses_dipoles) then
90       rrf = getRrf()
91       rt = getRt()      
92       call initialize_dipole(rrf, rt)
107         if (FF_uses_RF) then
108            dielect = getDielect()
109 <          call initialize_rf(rrf, rt, dielect)
109 >          call initialize_rf(dielect)
110         endif
111      else
112         if (FF_uses_RF) then          
# Line 100 | Line 114 | contains
114            thisStat = -1
115            return
116         endif
117 <    endif
117 >    endif
118  
119      if (FF_uses_LJ) then
120        
107       call getRcut(rcut)
108
121         select case (LJMIXPOLICY)
122         case (LB_MIXING_RULE)
123 <          call init_lj_FF(LB_MIXING_RULE, rcut, my_status)            
123 >          call init_lj_FF(LB_MIXING_RULE, my_status)            
124         case (EXPLICIT_MIXING_RULE)
125 <          call init_lj_FF(EXPLICIT_MIXING_RULE, rcut, my_status)
125 >          call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
126         case default
127            write(default_error,*) 'unknown LJ Mixing Policy!'
128            thisStat = -1
# Line 140 | Line 152 | contains
152  
153      if (FF_uses_GB .and. FF_uses_LJ) then
154      endif
155 +    if (.not. do_forces_initialized) then
156 +       !! Create neighbor lists
157 +       call expandNeighborList(getNlocal(), my_status)
158 +       if (my_Status /= 0) then
159 +          write(default_error,*) "SimSetup: ExpandNeighborList returned error."
160 +          thisStat = -1
161 +          return
162 +       endif
163 +    endif
164  
165 <
166 <    do_forces_initialized = .true.    
167 <
165 >    havePolicies = .true.
166 >    if( haveRlist ) do_forces_initialized = .true.
167 >    
168    end subroutine init_FF
169    
170  
# Line 167 | Line 188 | contains
188      logical ( kind = 2) :: do_pot_c, do_stress_c
189      logical :: do_pot
190      logical :: do_stress
191 < #ifdef IS_MPI
191 > #ifdef IS_MPI
192      real( kind = DP ) :: pot_local
193      integer :: nrow
194      integer :: ncol
# Line 177 | Line 198 | contains
198      logical :: update_nlist  
199      integer :: i, j, jbeg, jend, jnab
200      integer :: nlist
201 <    real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
201 >    real( kind = DP ) ::  rijsq
202      real(kind=dp),dimension(3) :: d
203      real(kind=dp) :: rfpot, mu_i, virial
204      integer :: me_i
# Line 186 | Line 207 | contains
207      integer :: listerror, error
208      integer :: localError
209  
210 +    real(kind=dp) :: listSkin = 1.0
211 +    
212 +
213      !! initialize local variables  
214  
215   #ifdef IS_MPI
216 +    pot_local = 0.0_dp
217      nlocal = getNlocal()
218      nrow   = getNrow(plan_row)
219      ncol   = getNcol(plan_col)
# Line 196 | Line 221 | contains
221      nlocal = getNlocal()
222      natoms = nlocal
223   #endif
224 <
200 <    call getRcut(rcut,rc2=rcutsq)
201 <    call getRlist(rlist,rlistsq)
202 <    
224 >  
225      call check_initialization(localError)
226      if ( localError .ne. 0 ) then
227         error = -1
# Line 229 | Line 251 | contains
251      
252      if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
253         !! See if we need to update neighbor lists
254 <       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
254 >       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
255         !! if_mpi_gather_stuff_for_prepair
256         !! do_prepair_loop_if_needed
257         !! if_mpi_scatter_stuff_from_prepair
258         !! if_mpi_gather_stuff_from_prepair_to_main_loop
259      else
260         !! See if we need to update neighbor lists
261 <       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
261 >       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
262      endif
263      
264   #ifdef IS_MPI
# Line 245 | Line 267 | contains
267        
268         !! save current configuration, construct neighbor list,
269         !! and calculate forces
270 <       call saveNeighborList(q)
270 >       call saveNeighborList(nlocal, q)
271        
272         neighborListSize = size(list)
273         nlist = 0      
# Line 259 | Line 281 | contains
281              
282               call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
283              
284 <             if (rijsq <  rlistsq) then            
284 >             if (rijsq < rlistsq) then            
285                  
286                  nlist = nlist + 1
287                  
# Line 275 | Line 297 | contains
297                  
298                  list(nlist) = j
299                                  
300 <                if (rijsq <  rcutsq) then
301 <                   call do_pair(i, j, rijsq, d, do_pot, do_stress, &
302 <                        u_l, A, f, t,pot)
281 <                endif
300 >                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
301 >                     u_l, A, f, t, pot_local)
302 >                
303               endif
304            enddo inner
305         enddo
# Line 299 | Line 320 | contains
320  
321                  call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
322                  call do_pair(i, j, rijsq, d, do_pot, do_stress, &
323 <                     u_l, A, f, t,pot)
323 >                     u_l, A, f, t, pot_local)
324  
325               enddo
326            endif
# Line 312 | Line 333 | contains
333        
334         ! save current configuration, contruct neighbor list,
335         ! and calculate forces
336 <       call saveNeighborList(q)
336 >       call saveNeighborList(natoms, q)
337        
338         neighborListSize = size(list)
339    
# Line 328 | Line 349 | contains
349               call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
350            
351  
352 <             if (rijsq <  rlistsq) then
352 >             if (rijsq < rlistsq) then
353                  
354                  nlist = nlist + 1
355                
# Line 344 | Line 365 | contains
365                  
366                  list(nlist) = j
367                  
368 <                if (rijsq <  rcutsq) then
369 <                   call do_pair(i, j, rijsq, d, do_pot, do_stress, &
370 <                        u_l, A, f, t,pot)
350 <                endif
368 >                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
369 >                        u_l, A, f, t, pot)
370 >                
371               endif
372            enddo inner
373         enddo
# Line 368 | Line 388 | contains
388  
389                  call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
390                  call do_pair(i, j, rijsq, d, do_pot, do_stress, &
391 <                     u_l, A, f, t,pot)
391 >                     u_l, A, f, t, pot)
392  
393               enddo
394            endif
# Line 411 | Line 431 | contains
431      if (do_pot) then
432         ! scatter/gather pot_row into the members of my column
433         call scatter(pot_Row, pot_Temp, plan_row)
434 <      
434 >
435         ! scatter/gather pot_local into all other procs
436         ! add resultant to get total pot
437         do i = 1, nlocal
438            pot_local = pot_local + pot_Temp(i)
439         enddo
440 +      
441 +       pot_Temp = 0.0_DP
442  
421       pot_Temp = 0.0_DP
422
443         call scatter(pot_Col, pot_Temp, plan_col)
444         do i = 1, nlocal
445            pot_local = pot_local + pot_Temp(i)
446         enddo
447 <      
447 >
448      endif    
449   #endif
450  
# Line 472 | Line 492 | contains
492   #ifdef IS_MPI
493  
494      if (do_pot) then
495 <       write(*,*) "Fortran is on pot:, pot, pot_local ", pot,pot_local
476 <       pot = pot_local
495 >       pot = pot + pot_local
496         !! we assume the c code will do the allreduce to get the total potential
497         !! we could do it right here if we needed to...
498      endif
499  
500      if (do_stress) then
501 <       call mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
501 >      call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
502              mpi_comm_world,mpi_err)
503 <       call mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
503 >       call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
504              mpi_comm_world,mpi_err)
505      endif
506  
# Line 496 | Line 515 | contains
515      
516    end subroutine do_force_loop
517  
518 <  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t,pot)
518 >  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
519  
520      real( kind = dp ) :: pot
521 <    real( kind = dp ), dimension(:,:) :: u_l
522 <    real (kind=dp), dimension(:,:) :: A
523 <    real (kind=dp), dimension(:,:) :: f
524 <    real (kind=dp), dimension(:,:) :: t
521 >    real( kind = dp ), dimension(3,getNlocal()) :: u_l
522 >    real (kind=dp), dimension(9,getNlocal()) :: A
523 >    real (kind=dp), dimension(3,getNlocal()) :: f
524 >    real (kind=dp), dimension(3,getNlocal()) :: t
525  
526      logical, intent(inout) :: do_pot, do_stress
527      integer, intent(in) :: i, j
# Line 518 | Line 537 | contains
537      r = sqrt(rijsq)
538  
539   #ifdef IS_MPI
540 +    if (tagRow(i) .eq. tagColumn(j)) then
541 +       write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
542 +    endif
543  
544      me_i = atid_row(i)
545      me_j = atid_col(j)
# Line 576 | Line 598 | contains
598         endif
599      endif
600      
601 +
602 +
603    end subroutine do_pair
604  
605  
606 +
607 +  subroutine do_preforce(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
608 +   real( kind = dp ) :: pot
609 +   real( kind = dp ), dimension(3,getNlocal()) :: u_l
610 +   real (kind=dp), dimension(9,getNlocal()) :: A
611 +   real (kind=dp), dimension(3,getNlocal()) :: f
612 +   real (kind=dp), dimension(3,getNlocal()) :: t
613 +  
614 +   logical, intent(inout) :: do_pot, do_stress
615 +   integer, intent(in) :: i, j
616 +   real ( kind = dp ), intent(inout)    :: rijsq
617 +   real ( kind = dp )                :: r
618 +   real ( kind = dp ), intent(inout) :: d(3)
619 +  
620 +   logical :: is_EAM_i, is_EAM_j
621 +  
622 +   integer :: me_i, me_j
623 +  
624 +   r = sqrt(rijsq)
625 +  
626 + #ifdef IS_MPI
627 +   if (tagRow(i) .eq. tagColumn(j)) then
628 +      write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
629 +   endif
630 +  
631 +   me_i = atid_row(i)
632 +   me_j = atid_col(j)
633 +  
634 + #else
635 +  
636 +   me_i = atid(i)
637 +   me_j = atid(j)
638 +  
639 + #endif
640 +  
641 +   if (FF_uses_EAM .and. SimUsesEAM()) then
642 +      call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
643 +      call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
644 +      
645 +      if ( is_EAM_i .and. is_EAM_j ) &
646 +           call calc_EAM_prepair(i, j, d, r, rijsq )
647 +   endif
648 +  end subroutine do_preforce
649 +  
650 +  
651    subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
652      
653      real (kind = dp), dimension(3) :: q_i
654      real (kind = dp), dimension(3) :: q_j
655      real ( kind = dp ), intent(out) :: r_sq
656 <    real( kind = dp ) :: d(3)
657 <    real( kind = dp ) :: d_old(3)
658 <    d(1:3) = q_i(1:3) - q_j(1:3)
659 <    d_old = d
656 >    real( kind = dp ) :: d(3), scaled(3)
657 >    integer i
658 >
659 >    d(1:3) = q_j(1:3) - q_i(1:3)
660 >
661      ! Wrap back into periodic box if necessary
662      if ( SimUsesPBC() ) then
663        
664 <       d(1:3) = d(1:3) - box(1:3) * sign(1.0_dp,d(1:3)) * &
665 <            int(abs(d(1:3)/box(1:3)) + 0.5_dp)
664 >       if( .not.boxIsOrthorhombic ) then
665 >          ! calc the scaled coordinates.
666 >          
667 >          scaled = matmul(HmatInv, d)
668 >          
669 >          ! wrap the scaled coordinates
670 >
671 >          scaled = scaled  - anint(scaled)
672 >          
673 >
674 >          ! calc the wrapped real coordinates from the wrapped scaled
675 >          ! coordinates
676 >
677 >          d = matmul(Hmat,scaled)
678 >
679 >       else
680 >          ! calc the scaled coordinates.
681 >          
682 >          do i = 1, 3
683 >             scaled(i) = d(i) * HmatInv(i,i)
684 >            
685 >             ! wrap the scaled coordinates
686 >            
687 >             scaled(i) = scaled(i) - anint(scaled(i))
688 >            
689 >             ! calc the wrapped real coordinates from the wrapped scaled
690 >             ! coordinates
691 >
692 >             d(i) = scaled(i)*Hmat(i,i)
693 >          enddo
694 >       endif
695        
696      endif
697 +    
698      r_sq = dot_product(d,d)
699 <        
699 >    
700    end subroutine get_interatomic_vector
701 <
701 >  
702    subroutine check_initialization(error)
703      integer, intent(out) :: error
704      
# Line 655 | Line 755 | contains
755      rf = 0.0_dp
756      tau_Temp = 0.0_dp
757      virial_Temp = 0.0_dp
658    
758    end subroutine zero_work_arrays
759    
760    function skipThisPair(atom1, atom2) result(skip_it)
# Line 699 | Line 798 | contains
798   #else
799      unique_id_2 = atom2
800   #endif
801 <    
801 >
802   #ifdef IS_MPI
803      !! this situation should only arise in MPI simulations
804      if (unique_id_1 == unique_id_2) then
# Line 709 | Line 808 | contains
808      
809      !! this prevents us from doing the pair on multiple processors
810      if (unique_id_1 < unique_id_2) then
811 <       if (mod(unique_id_1 + unique_id_2,2) == 0) skip_it = .true.
812 <       return
811 >       if (mod(unique_id_1 + unique_id_2,2) == 0) then
812 >          skip_it = .true.
813 >          return
814 >       endif
815      else                
816 <       if (mod(unique_id_1 + unique_id_2,2) == 1) skip_it = .true.
817 <       return
816 >       if (mod(unique_id_1 + unique_id_2,2) == 1) then
817 >          skip_it = .true.
818 >          return
819 >       endif
820      endif
821   #endif
822 <
822 >
823      !! the rest of these situations can happen in all simulations:
824      do i = 1, nExcludes_global      
825         if ((excludesGlobal(i) == unique_id_1) .or. &
# Line 725 | Line 828 | contains
828            return
829         endif
830      enddo
831 <
831 >
832      do i = 1, nExcludes_local
833         if (excludesLocal(1,i) == unique_id_1) then
834            if (excludesLocal(2,i) == unique_id_2) then

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines