ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-3.0/src/UseTheForce/doForces.F90
(Generate patch)

Comparing trunk/OOPSE-3.0/src/UseTheForce/doForces.F90 (file contents):
Revision 2228 by kdaily, Tue May 17 02:09:25 2005 UTC vs.
Revision 2229 by chrisfen, Tue May 17 22:35:01 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.16 2005-05-17 02:09:06 kdaily Exp $, $Date: 2005-05-17 02:09:06 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
48 > !! @version $Id: doForces.F90,v 1.17 2005-05-17 22:35:01 chrisfen Exp $, $Date: 2005-05-17 22:35:01 $, $Name: not supported by cvs2svn $, $Revision: 1.17 $
49  
50  
51   module doForces
# Line 82 | Line 82 | module doForces
82    logical, save :: haveSIMvariables = .false.
83    logical, save :: havePropertyMap = .false.
84    logical, save :: haveSaneForceField = .false.
85 <  
85 >
86    logical, save :: FF_uses_DirectionalAtoms
87    logical, save :: FF_uses_LennardJones
88    logical, save :: FF_uses_Electrostatics
89    logical, save :: FF_uses_Charges
90    logical, save :: FF_uses_Dipoles
91    logical, save :: FF_uses_Quadrupoles
92 <  logical, save :: FF_uses_sticky
92 >  logical, save :: FF_uses_Sticky
93 >  logical, save :: FF_uses_StickyPower
94    logical, save :: FF_uses_GayBerne
95    logical, save :: FF_uses_EAM
96    logical, save :: FF_uses_Shapes
# Line 103 | Line 104 | module doForces
104    logical, save :: SIM_uses_Dipoles
105    logical, save :: SIM_uses_Quadrupoles
106    logical, save :: SIM_uses_Sticky
107 +  logical, save :: SIM_uses_StickyPower
108    logical, save :: SIM_uses_GayBerne
109    logical, save :: SIM_uses_EAM
110    logical, save :: SIM_uses_Shapes
# Line 134 | Line 136 | module doForces
136       logical :: is_Dipole        = .false.
137       logical :: is_Quadrupole    = .false.
138       logical :: is_Sticky        = .false.
139 +     logical :: is_StickyPower   = .false.
140       logical :: is_GayBerne      = .false.
141       logical :: is_EAM           = .false.
142       logical :: is_Shape         = .false.
# Line 145 | Line 148 | contains
148   contains
149  
150    subroutine setRlistDF( this_rlist )
151 <    
151 >
152      real(kind=dp) :: this_rlist
153  
154      rlist = this_rlist
155      rlistsq = rlist * rlist
156 <    
156 >
157      haveRlist = .true.
158  
159 <  end subroutine setRlistDF    
159 >  end subroutine setRlistDF
160  
161    subroutine createPropertyMap(status)
162      integer :: nAtypes
# Line 170 | Line 173 | contains
173         status = -1
174         return
175      end if
176 <        
176 >
177      if (.not. allocated(PropertyMap)) then
178         allocate(PropertyMap(nAtypes))
179      endif
# Line 181 | Line 184 | contains
184  
185         call getElementProperty(atypes, i, "is_LennardJones", thisProperty)
186         PropertyMap(i)%is_LennardJones = thisProperty
187 <      
187 >
188         call getElementProperty(atypes, i, "is_Electrostatic", thisProperty)
189         PropertyMap(i)%is_Electrostatic = thisProperty
190  
191         call getElementProperty(atypes, i, "is_Charge", thisProperty)
192         PropertyMap(i)%is_Charge = thisProperty
193 <      
193 >
194         call getElementProperty(atypes, i, "is_Dipole", thisProperty)
195         PropertyMap(i)%is_Dipole = thisProperty
196  
# Line 196 | Line 199 | contains
199  
200         call getElementProperty(atypes, i, "is_Sticky", thisProperty)
201         PropertyMap(i)%is_Sticky = thisProperty
202 +      
203 +       call getElementProperty(atypes, i, "is_StickyPower", thisProperty)
204 +       PropertyMap(i)%is_StickyPower = thisProperty
205  
206         call getElementProperty(atypes, i, "is_GayBerne", thisProperty)
207         PropertyMap(i)%is_GayBerne = thisProperty
# Line 221 | Line 227 | contains
227      SIM_uses_Charges = SimUsesCharges()
228      SIM_uses_Dipoles = SimUsesDipoles()
229      SIM_uses_Sticky = SimUsesSticky()
230 +    SIM_uses_StickyPower = SimUsesStickyPower()
231      SIM_uses_GayBerne = SimUsesGayBerne()
232      SIM_uses_EAM = SimUsesEAM()
233      SIM_uses_Shapes = SimUsesShapes()
# Line 241 | Line 248 | contains
248      integer :: myStatus
249  
250      error = 0
251 <    
251 >
252      if (.not. havePropertyMap) then
253  
254         myStatus = 0
# Line 286 | Line 293 | contains
293   #endif
294      return
295    end subroutine doReadyCheck
289    
296  
297 +
298    subroutine init_FF(use_RF_c, thisStat)
299  
300      logical, intent(in) :: use_RF_c
# Line 302 | Line 309 | contains
309  
310      !! Fortran's version of a cast:
311      FF_uses_RF = use_RF_c
312 <    
312 >
313      !! init_FF is called *after* all of the atom types have been
314      !! defined in atype_module using the new_atype subroutine.
315      !!
316      !! this will scan through the known atypes and figure out what
317      !! interactions are used by the force field.    
318 <  
318 >
319      FF_uses_DirectionalAtoms = .false.
320      FF_uses_LennardJones = .false.
321      FF_uses_Electrostatics = .false.
322      FF_uses_Charges = .false.    
323      FF_uses_Dipoles = .false.
324      FF_uses_Sticky = .false.
325 +    FF_uses_StickyPower = .false.
326      FF_uses_GayBerne = .false.
327      FF_uses_EAM = .false.
328      FF_uses_Shapes = .false.
329      FF_uses_FLARB = .false.
330 <    
330 >
331      call getMatchingElementList(atypes, "is_Directional", .true., &
332           nMatches, MatchList)
333      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
# Line 327 | Line 335 | contains
335      call getMatchingElementList(atypes, "is_LennardJones", .true., &
336           nMatches, MatchList)
337      if (nMatches .gt. 0) FF_uses_LennardJones = .true.
338 <    
338 >
339      call getMatchingElementList(atypes, "is_Electrostatic", .true., &
340           nMatches, MatchList)
341      if (nMatches .gt. 0) then
# Line 340 | Line 348 | contains
348         FF_uses_Charges = .true.  
349         FF_uses_Electrostatics = .true.
350      endif
351 <    
351 >
352      call getMatchingElementList(atypes, "is_Dipole", .true., &
353           nMatches, MatchList)
354      if (nMatches .gt. 0) then
# Line 356 | Line 364 | contains
364         FF_uses_Electrostatics = .true.
365         FF_uses_DirectionalAtoms = .true.
366      endif
367 <    
367 >
368      call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
369           MatchList)
370      if (nMatches .gt. 0) then
371         FF_uses_Sticky = .true.
372         FF_uses_DirectionalAtoms = .true.
373      endif
374 +
375 +    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
376 +         MatchList)
377 +    if (nMatches .gt. 0) then
378 +       FF_uses_StickyPower = .true.
379 +       FF_uses_DirectionalAtoms = .true.
380 +    endif
381      
382      call getMatchingElementList(atypes, "is_GayBerne", .true., &
383           nMatches, MatchList)
# Line 370 | Line 385 | contains
385         FF_uses_GayBerne = .true.
386         FF_uses_DirectionalAtoms = .true.
387      endif
388 <    
388 >
389      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
390      if (nMatches .gt. 0) FF_uses_EAM = .true.
391 <    
391 >
392      call getMatchingElementList(atypes, "is_Shape", .true., &
393           nMatches, MatchList)
394      if (nMatches .gt. 0) then
# Line 387 | Line 402 | contains
402  
403      !! Assume sanity (for the sake of argument)
404      haveSaneForceField = .true.
405 <    
405 >
406      !! check to make sure the FF_uses_RF setting makes sense
407 <    
407 >
408      if (FF_uses_dipoles) then
409         if (FF_uses_RF) then
410            dielect = getDielect()
# Line 402 | Line 417 | contains
417            haveSaneForceField = .false.
418            return
419         endif
420 <    endif
420 >    endif
421  
422      !sticky module does not contain check_sticky_FF anymore
423      !if (FF_uses_sticky) then
# Line 415 | Line 430 | contains
430      !endif
431  
432      if (FF_uses_EAM) then
433 <         call init_EAM_FF(my_status)
433 >       call init_EAM_FF(my_status)
434         if (my_status /= 0) then
435            write(default_error, *) "init_EAM_FF returned a bad status"
436            thisStat = -1
# Line 435 | Line 450 | contains
450  
451      if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
452      endif
453 <    
453 >
454      if (.not. haveNeighborList) then
455         !! Create neighbor lists
456         call expandNeighborList(nLocal, my_status)
# Line 445 | Line 460 | contains
460            return
461         endif
462         haveNeighborList = .true.
463 <    endif    
464 <    
463 >    endif
464 >
465    end subroutine init_FF
451  
466  
467 +
468    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
469    !------------------------------------------------------------->
470    subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
# Line 501 | Line 516 | contains
516      integer :: loopStart, loopEnd, loop
517  
518      real(kind=dp) :: listSkin = 1.0  
519 <    
519 >
520      !! initialize local variables  
521 <    
521 >
522   #ifdef IS_MPI
523      pot_local = 0.0_dp
524      nAtomsInRow   = getNatomsInRow(plan_atom_row)
# Line 513 | Line 528 | contains
528   #else
529      natoms = nlocal
530   #endif
531 <    
531 >
532      call doReadyCheck(localError)
533      if ( localError .ne. 0 ) then
534         call handleError("do_force_loop", "Not Initialized")
# Line 521 | Line 536 | contains
536         return
537      end if
538      call zero_work_arrays()
539 <        
539 >
540      do_pot = do_pot_c
541      do_stress = do_stress_c
542 <    
542 >
543      ! Gather all information needed by all force loops:
544 <    
544 >
545   #ifdef IS_MPI    
546 <    
546 >
547      call gather(q, q_Row, plan_atom_row_3d)
548      call gather(q, q_Col, plan_atom_col_3d)
549  
550      call gather(q_group, q_group_Row, plan_group_row_3d)
551      call gather(q_group, q_group_Col, plan_group_col_3d)
552 <        
552 >
553      if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
554         call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
555         call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
556 <      
556 >
557         call gather(A, A_Row, plan_atom_row_rotation)
558         call gather(A, A_Col, plan_atom_col_rotation)
559      endif
560 <    
560 >
561   #endif
562 <    
562 >
563      !! Begin force loop timing:
564   #ifdef PROFILE
565      call cpu_time(forceTimeInitial)
566      nloops = nloops + 1
567   #endif
568 <    
568 >
569      loopEnd = PAIR_LOOP
570      if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
571         loopStart = PREPAIR_LOOP
# Line 565 | Line 580 | contains
580         if (loop .eq. loopStart) then
581   #ifdef IS_MPI
582            call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
583 <             update_nlist)
583 >               update_nlist)
584   #else
585            call checkNeighborList(nGroups, q_group, listSkin, &
586 <             update_nlist)
586 >               update_nlist)
587   #endif
588         endif
589 <      
589 >
590         if (update_nlist) then
591            !! save current configuration and construct neighbor list
592   #ifdef IS_MPI
# Line 582 | Line 597 | contains
597            neighborListSize = size(list)
598            nlist = 0
599         endif
600 <      
600 >
601         istart = 1
602   #ifdef IS_MPI
603         iend = nGroupsInRow
# Line 592 | Line 607 | contains
607         outer: do i = istart, iend
608  
609            if (update_nlist) point(i) = nlist + 1
610 <          
610 >
611            n_in_i = groupStartRow(i+1) - groupStartRow(i)
612 <          
612 >
613            if (update_nlist) then
614   #ifdef IS_MPI
615               jstart = 1
# Line 609 | Line 624 | contains
624               ! make sure group i has neighbors
625               if (jstart .gt. jend) cycle outer
626            endif
627 <          
627 >
628            do jnab = jstart, jend
629               if (update_nlist) then
630                  j = jnab
# Line 628 | Line 643 | contains
643               if (rgrpsq < rlistsq) then
644                  if (update_nlist) then
645                     nlist = nlist + 1
646 <                  
646 >
647                     if (nlist > neighborListSize) then
648   #ifdef IS_MPI                
649                        call expandNeighborList(nGroupsInRow, listerror)
# Line 642 | Line 657 | contains
657                        end if
658                        neighborListSize = size(list)
659                     endif
660 <                  
660 >
661                     list(nlist) = j
662                  endif
663 <                
663 >
664                  if (loop .eq. PAIR_LOOP) then
665                     vij = 0.0d0
666                     fij(1:3) = 0.0d0
667                  endif
668 <                
668 >
669                  call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
670                       in_switching_region)
671 <                
672 <                n_in_j = groupStartCol(j+1) - groupStartCol(j)
673 <                
671 >
672 >                n_in_j = groupStartCol(j+1) - groupStartCol(j)
673 >
674                  do ia = groupStartRow(i), groupStartRow(i+1)-1
675 <                  
675 >
676                     atom1 = groupListRow(ia)
677 <                  
677 >
678                     inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
679 <                      
679 >
680                        atom2 = groupListCol(jb)
681 <                      
681 >
682                        if (skipThisPair(atom1, atom2)) cycle inner
683  
684                        if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
# Line 705 | Line 720 | contains
720                        endif
721                     enddo inner
722                  enddo
723 <                
723 >
724                  if (loop .eq. PAIR_LOOP) then
725                     if (in_switching_region) then
726                        swderiv = vij*dswdr/rgrp
727                        fij(1) = fij(1) + swderiv*d_grp(1)
728                        fij(2) = fij(2) + swderiv*d_grp(2)
729                        fij(3) = fij(3) + swderiv*d_grp(3)
730 <                      
730 >
731                        do ia=groupStartRow(i), groupStartRow(i+1)-1
732                           atom1=groupListRow(ia)
733                           mf = mfactRow(atom1)
# Line 726 | Line 741 | contains
741                           f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
742   #endif
743                        enddo
744 <                      
744 >
745                        do jb=groupStartCol(j), groupStartCol(j+1)-1
746                           atom2=groupListCol(jb)
747                           mf = mfactCol(atom2)
# Line 741 | Line 756 | contains
756   #endif
757                        enddo
758                     endif
759 <                  
759 >
760                     if (do_stress) call add_stress_tensor(d_grp, fij)
761                  endif
762               end if
763            enddo
764         enddo outer
765 <      
765 >
766         if (update_nlist) then
767   #ifdef IS_MPI
768            point(nGroupsInRow + 1) = nlist + 1
# Line 761 | Line 776 | contains
776               update_nlist = .false.                              
777            endif
778         endif
779 <            
779 >
780         if (loop .eq. PREPAIR_LOOP) then
781            call do_preforce(nlocal, pot)
782         endif
783 <      
783 >
784      enddo
785 <    
785 >
786      !! Do timing
787   #ifdef PROFILE
788      call cpu_time(forceTimeFinal)
789      forceTime = forceTime + forceTimeFinal - forceTimeInitial
790   #endif    
791 <    
791 >
792   #ifdef IS_MPI
793      !!distribute forces
794 <    
794 >
795      f_temp = 0.0_dp
796      call scatter(f_Row,f_temp,plan_atom_row_3d)
797      do i = 1,nlocal
798         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
799      end do
800 <    
800 >
801      f_temp = 0.0_dp
802      call scatter(f_Col,f_temp,plan_atom_col_3d)
803      do i = 1,nlocal
804         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
805      end do
806 <    
806 >
807      if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
808         t_temp = 0.0_dp
809         call scatter(t_Row,t_temp,plan_atom_row_3d)
# Line 797 | Line 812 | contains
812         end do
813         t_temp = 0.0_dp
814         call scatter(t_Col,t_temp,plan_atom_col_3d)
815 <      
815 >
816         do i = 1,nlocal
817            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
818         end do
819      endif
820 <    
820 >
821      if (do_pot) then
822         ! scatter/gather pot_row into the members of my column
823         call scatter(pot_Row, pot_Temp, plan_atom_row)
824 <      
824 >
825         ! scatter/gather pot_local into all other procs
826         ! add resultant to get total pot
827         do i = 1, nlocal
828            pot_local = pot_local + pot_Temp(i)
829         enddo
830 <      
830 >
831         pot_Temp = 0.0_DP
832 <      
832 >
833         call scatter(pot_Col, pot_Temp, plan_atom_col)
834         do i = 1, nlocal
835            pot_local = pot_local + pot_Temp(i)
836         enddo
837 <      
837 >
838      endif
839   #endif
840 <    
840 >
841      if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
842 <      
842 >
843         if (FF_uses_RF .and. SIM_uses_RF) then
844 <          
844 >
845   #ifdef IS_MPI
846            call scatter(rf_Row,rf,plan_atom_row_3d)
847            call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
# Line 834 | Line 849 | contains
849               rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
850            end do
851   #endif
852 <          
852 >
853            do i = 1, nLocal
854 <            
854 >
855               rfpot = 0.0_DP
856   #ifdef IS_MPI
857               me_i = atid_row(i)
858   #else
859               me_i = atid(i)
860   #endif
861 <            
861 >
862               if (PropertyMap(me_i)%is_Dipole) then
863 <                
863 >
864                  mu_i = getDipoleMoment(me_i)
865 <    
865 >
866                  !! The reaction field needs to include a self contribution
867                  !! to the field:
868                  call accumulate_self_rf(i, mu_i, eFrame)
# Line 858 | Line 873 | contains
873                  pot_local = pot_local + rfpot
874   #else
875                  pot = pot + rfpot
876 <      
876 >
877   #endif
878 <             endif            
878 >             endif
879            enddo
880         endif
881      endif
882 <    
883 <    
882 >
883 >
884   #ifdef IS_MPI
885 <    
885 >
886      if (do_pot) then
887         pot = pot + pot_local
888         !! we assume the c code will do the allreduce to get the total potential
889         !! we could do it right here if we needed to...
890      endif
891 <    
891 >
892      if (do_stress) then
893         call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
894              mpi_comm_world,mpi_err)
895         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
896              mpi_comm_world,mpi_err)
897      endif
898 <    
898 >
899   #else
900 <    
900 >
901      if (do_stress) then
902         tau = tau_Temp
903         virial = virial_Temp
904      endif
905 <    
905 >
906   #endif
907 <      
907 >
908    end subroutine do_force_loop
909 <  
909 >
910    subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
911         eFrame, A, f, t, pot, vpair, fpair)
912  
# Line 922 | Line 937 | contains
937      me_j = atid(j)
938   #endif
939  
940 < !    write(*,*) i, j, me_i, me_j
941 <    
940 >    !    write(*,*) i, j, me_i, me_j
941 >
942      if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then
943 <      
943 >
944         if ( PropertyMap(me_i)%is_LennardJones .and. &
945              PropertyMap(me_j)%is_LennardJones ) then
946            call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
947         endif
948 <      
948 >
949      endif
950 <    
950 >
951      if (FF_uses_Electrostatics .and. SIM_uses_Electrostatics) then
952 <      
952 >
953         if (PropertyMap(me_i)%is_Electrostatic .and. &
954              PropertyMap(me_j)%is_Electrostatic) then
955            call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
956                 pot, eFrame, f, t, do_pot)
957         endif
958 <      
958 >
959         if (FF_uses_dipoles .and. SIM_uses_dipoles) then      
960            if ( PropertyMap(me_i)%is_Dipole .and. &
961                 PropertyMap(me_j)%is_Dipole) then
# Line 959 | Line 974 | contains
974            call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
975                 pot, A, f, t, do_pot)
976         endif
977 <      
977 >
978      endif
979  
980 <
980 >    if (FF_uses_StickyPower .and. SIM_uses_stickypower) then
981 >       if ( PropertyMap(me_i)%is_StickyPower .and. &
982 >            PropertyMap(me_j)%is_StickyPower) then
983 >          call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
984 >               pot, A, f, t, do_pot)
985 >       endif
986 >    endif
987 >    
988      if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then
989 <      
989 >
990         if ( PropertyMap(me_i)%is_GayBerne .and. &
991              PropertyMap(me_j)%is_GayBerne) then
992            call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
993                 pot, A, f, t, do_pot)
994         endif
995 <      
995 >
996      endif
997 <    
997 >
998      if (FF_uses_EAM .and. SIM_uses_EAM) then
999 <      
999 >
1000         if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1001            call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1002                 do_pot)
1003         endif
1004 <      
1004 >
1005      endif
1006  
1007  
1008 < !    write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
1008 >    !    write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
1009  
1010      if (FF_uses_Shapes .and. SIM_uses_Shapes) then
1011         if ( PropertyMap(me_i)%is_Shape .and. &
# Line 991 | Line 1013 | contains
1013            call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1014                 pot, A, f, t, do_pot)
1015         endif
1016 <      
1016 >       if ( (PropertyMap(me_i)%is_Shape .and. &
1017 >            PropertyMap(me_j)%is_LennardJones) .or. &
1018 >            (PropertyMap(me_i)%is_LennardJones .and. &
1019 >            PropertyMap(me_j)%is_Shape) ) then
1020 >          call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1021 >               pot, A, f, t, do_pot)
1022 >       endif
1023      endif
1024 <    
1024 >
1025    end subroutine do_pair
1026  
1027    subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
1028         do_pot, do_stress, eFrame, A, f, t, pot)
1029  
1030 <   real( kind = dp ) :: pot, sw
1031 <   real( kind = dp ), dimension(9,nLocal) :: eFrame
1032 <   real (kind=dp), dimension(9,nLocal) :: A
1033 <   real (kind=dp), dimension(3,nLocal) :: f
1034 <   real (kind=dp), dimension(3,nLocal) :: t
1007 <  
1008 <   logical, intent(inout) :: do_pot, do_stress
1009 <   integer, intent(in) :: i, j
1010 <   real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1011 <   real ( kind = dp )                :: r, rc
1012 <   real ( kind = dp ), intent(inout) :: d(3), dc(3)
1013 <  
1014 <   logical :: is_EAM_i, is_EAM_j
1015 <  
1016 <   integer :: me_i, me_j
1017 <  
1030 >    real( kind = dp ) :: pot, sw
1031 >    real( kind = dp ), dimension(9,nLocal) :: eFrame
1032 >    real (kind=dp), dimension(9,nLocal) :: A
1033 >    real (kind=dp), dimension(3,nLocal) :: f
1034 >    real (kind=dp), dimension(3,nLocal) :: t
1035  
1036 +    logical, intent(inout) :: do_pot, do_stress
1037 +    integer, intent(in) :: i, j
1038 +    real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1039 +    real ( kind = dp )                :: r, rc
1040 +    real ( kind = dp ), intent(inout) :: d(3), dc(3)
1041 +
1042 +    logical :: is_EAM_i, is_EAM_j
1043 +
1044 +    integer :: me_i, me_j
1045 +
1046 +
1047      r = sqrt(rijsq)
1048      if (SIM_uses_molecular_cutoffs) then
1049         rc = sqrt(rcijsq)
1050      else
1051         rc = r
1052      endif
1025  
1053  
1054 +
1055   #ifdef IS_MPI  
1056 <   me_i = atid_row(i)
1057 <   me_j = atid_col(j)  
1056 >    me_i = atid_row(i)
1057 >    me_j = atid_col(j)  
1058   #else  
1059 <   me_i = atid(i)
1060 <   me_j = atid(j)  
1059 >    me_i = atid(i)
1060 >    me_j = atid(j)  
1061   #endif
1034  
1035   if (FF_uses_EAM .and. SIM_uses_EAM) then
1036      
1037      if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1038           call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1039      
1040   endif
1041  
1042 end subroutine do_prepair
1043
1044
1045 subroutine do_preforce(nlocal,pot)
1046   integer :: nlocal
1047   real( kind = dp ) :: pot
1048  
1049   if (FF_uses_EAM .and. SIM_uses_EAM) then
1050      call calc_EAM_preforce_Frho(nlocal,pot)
1051   endif
1052  
1053  
1054 end subroutine do_preforce
1055
1056
1057 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1058  
1059   real (kind = dp), dimension(3) :: q_i
1060   real (kind = dp), dimension(3) :: q_j
1061   real ( kind = dp ), intent(out) :: r_sq
1062   real( kind = dp ) :: d(3), scaled(3)
1063   integer i
1064  
1065   d(1:3) = q_j(1:3) - q_i(1:3)
1066  
1067   ! Wrap back into periodic box if necessary
1068   if ( SIM_uses_PBC ) then
1069      
1070      if( .not.boxIsOrthorhombic ) then
1071         ! calc the scaled coordinates.
1072        
1073         scaled = matmul(HmatInv, d)
1074        
1075         ! wrap the scaled coordinates
1076        
1077         scaled = scaled  - anint(scaled)
1078        
1079        
1080         ! calc the wrapped real coordinates from the wrapped scaled
1081         ! coordinates
1082        
1083         d = matmul(Hmat,scaled)
1084        
1085      else
1086         ! calc the scaled coordinates.
1087        
1088         do i = 1, 3
1089            scaled(i) = d(i) * HmatInv(i,i)
1090            
1091            ! wrap the scaled coordinates
1092            
1093            scaled(i) = scaled(i) - anint(scaled(i))
1094            
1095            ! calc the wrapped real coordinates from the wrapped scaled
1096            ! coordinates
1097            
1098            d(i) = scaled(i)*Hmat(i,i)
1099         enddo
1100      endif
1101      
1102   endif
1103  
1104   r_sq = dot_product(d,d)
1105  
1106 end subroutine get_interatomic_vector
1107
1108 subroutine zero_work_arrays()
1109  
1110 #ifdef IS_MPI
1111  
1112   q_Row = 0.0_dp
1113   q_Col = 0.0_dp
1062  
1063 <   q_group_Row = 0.0_dp
1064 <   q_group_Col = 0.0_dp  
1065 <  
1066 <   eFrame_Row = 0.0_dp
1067 <   eFrame_Col = 0.0_dp
1068 <  
1069 <   A_Row = 0.0_dp
1070 <   A_Col = 0.0_dp
1071 <  
1072 <   f_Row = 0.0_dp
1073 <   f_Col = 0.0_dp
1074 <   f_Temp = 0.0_dp
1075 <  
1076 <   t_Row = 0.0_dp
1077 <   t_Col = 0.0_dp
1078 <   t_Temp = 0.0_dp
1079 <  
1080 <   pot_Row = 0.0_dp
1081 <   pot_Col = 0.0_dp
1082 <   pot_Temp = 0.0_dp
1083 <  
1084 <   rf_Row = 0.0_dp
1085 <   rf_Col = 0.0_dp
1086 <   rf_Temp = 0.0_dp
1087 <  
1063 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1064 >
1065 >       if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1066 >            call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1067 >
1068 >    endif
1069 >
1070 >  end subroutine do_prepair
1071 >
1072 >
1073 >  subroutine do_preforce(nlocal,pot)
1074 >    integer :: nlocal
1075 >    real( kind = dp ) :: pot
1076 >
1077 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1078 >       call calc_EAM_preforce_Frho(nlocal,pot)
1079 >    endif
1080 >
1081 >
1082 >  end subroutine do_preforce
1083 >
1084 >
1085 >  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1086 >
1087 >    real (kind = dp), dimension(3) :: q_i
1088 >    real (kind = dp), dimension(3) :: q_j
1089 >    real ( kind = dp ), intent(out) :: r_sq
1090 >    real( kind = dp ) :: d(3), scaled(3)
1091 >    integer i
1092 >
1093 >    d(1:3) = q_j(1:3) - q_i(1:3)
1094 >
1095 >    ! Wrap back into periodic box if necessary
1096 >    if ( SIM_uses_PBC ) then
1097 >
1098 >       if( .not.boxIsOrthorhombic ) then
1099 >          ! calc the scaled coordinates.
1100 >
1101 >          scaled = matmul(HmatInv, d)
1102 >
1103 >          ! wrap the scaled coordinates
1104 >
1105 >          scaled = scaled  - anint(scaled)
1106 >
1107 >
1108 >          ! calc the wrapped real coordinates from the wrapped scaled
1109 >          ! coordinates
1110 >
1111 >          d = matmul(Hmat,scaled)
1112 >
1113 >       else
1114 >          ! calc the scaled coordinates.
1115 >
1116 >          do i = 1, 3
1117 >             scaled(i) = d(i) * HmatInv(i,i)
1118 >
1119 >             ! wrap the scaled coordinates
1120 >
1121 >             scaled(i) = scaled(i) - anint(scaled(i))
1122 >
1123 >             ! calc the wrapped real coordinates from the wrapped scaled
1124 >             ! coordinates
1125 >
1126 >             d(i) = scaled(i)*Hmat(i,i)
1127 >          enddo
1128 >       endif
1129 >
1130 >    endif
1131 >
1132 >    r_sq = dot_product(d,d)
1133 >
1134 >  end subroutine get_interatomic_vector
1135 >
1136 >  subroutine zero_work_arrays()
1137 >
1138 > #ifdef IS_MPI
1139 >
1140 >    q_Row = 0.0_dp
1141 >    q_Col = 0.0_dp
1142 >
1143 >    q_group_Row = 0.0_dp
1144 >    q_group_Col = 0.0_dp  
1145 >
1146 >    eFrame_Row = 0.0_dp
1147 >    eFrame_Col = 0.0_dp
1148 >
1149 >    A_Row = 0.0_dp
1150 >    A_Col = 0.0_dp
1151 >
1152 >    f_Row = 0.0_dp
1153 >    f_Col = 0.0_dp
1154 >    f_Temp = 0.0_dp
1155 >
1156 >    t_Row = 0.0_dp
1157 >    t_Col = 0.0_dp
1158 >    t_Temp = 0.0_dp
1159 >
1160 >    pot_Row = 0.0_dp
1161 >    pot_Col = 0.0_dp
1162 >    pot_Temp = 0.0_dp
1163 >
1164 >    rf_Row = 0.0_dp
1165 >    rf_Col = 0.0_dp
1166 >    rf_Temp = 0.0_dp
1167 >
1168   #endif
1169 <
1170 <   if (FF_uses_EAM .and. SIM_uses_EAM) then
1171 <      call clean_EAM()
1172 <   endif
1173 <  
1174 <   rf = 0.0_dp
1175 <   tau_Temp = 0.0_dp
1176 <   virial_Temp = 0.0_dp
1177 < end subroutine zero_work_arrays
1178 <
1179 < function skipThisPair(atom1, atom2) result(skip_it)
1180 <   integer, intent(in) :: atom1
1181 <   integer, intent(in), optional :: atom2
1182 <   logical :: skip_it
1183 <   integer :: unique_id_1, unique_id_2
1184 <   integer :: me_i,me_j
1185 <   integer :: i
1186 <  
1187 <   skip_it = .false.
1188 <  
1189 <   !! there are a number of reasons to skip a pair or a particle
1190 <   !! mostly we do this to exclude atoms who are involved in short
1191 <   !! range interactions (bonds, bends, torsions), but we also need
1192 <   !! to exclude some overcounted interactions that result from
1193 <   !! the parallel decomposition
1194 <  
1169 >
1170 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1171 >       call clean_EAM()
1172 >    endif
1173 >
1174 >    rf = 0.0_dp
1175 >    tau_Temp = 0.0_dp
1176 >    virial_Temp = 0.0_dp
1177 >  end subroutine zero_work_arrays
1178 >
1179 >  function skipThisPair(atom1, atom2) result(skip_it)
1180 >    integer, intent(in) :: atom1
1181 >    integer, intent(in), optional :: atom2
1182 >    logical :: skip_it
1183 >    integer :: unique_id_1, unique_id_2
1184 >    integer :: me_i,me_j
1185 >    integer :: i
1186 >
1187 >    skip_it = .false.
1188 >
1189 >    !! there are a number of reasons to skip a pair or a particle
1190 >    !! mostly we do this to exclude atoms who are involved in short
1191 >    !! range interactions (bonds, bends, torsions), but we also need
1192 >    !! to exclude some overcounted interactions that result from
1193 >    !! the parallel decomposition
1194 >
1195   #ifdef IS_MPI
1196 <   !! in MPI, we have to look up the unique IDs for each atom
1197 <   unique_id_1 = AtomRowToGlobal(atom1)
1196 >    !! in MPI, we have to look up the unique IDs for each atom
1197 >    unique_id_1 = AtomRowToGlobal(atom1)
1198   #else
1199 <   !! in the normal loop, the atom numbers are unique
1200 <   unique_id_1 = atom1
1199 >    !! in the normal loop, the atom numbers are unique
1200 >    unique_id_1 = atom1
1201   #endif
1202 <  
1203 <   !! We were called with only one atom, so just check the global exclude
1204 <   !! list for this atom
1205 <   if (.not. present(atom2)) then
1206 <      do i = 1, nExcludes_global
1207 <         if (excludesGlobal(i) == unique_id_1) then
1208 <            skip_it = .true.
1209 <            return
1210 <         end if
1211 <      end do
1212 <      return
1213 <   end if
1214 <  
1202 >
1203 >    !! We were called with only one atom, so just check the global exclude
1204 >    !! list for this atom
1205 >    if (.not. present(atom2)) then
1206 >       do i = 1, nExcludes_global
1207 >          if (excludesGlobal(i) == unique_id_1) then
1208 >             skip_it = .true.
1209 >             return
1210 >          end if
1211 >       end do
1212 >       return
1213 >    end if
1214 >
1215   #ifdef IS_MPI
1216 <   unique_id_2 = AtomColToGlobal(atom2)
1216 >    unique_id_2 = AtomColToGlobal(atom2)
1217   #else
1218 <   unique_id_2 = atom2
1218 >    unique_id_2 = atom2
1219   #endif
1220 <  
1220 >
1221   #ifdef IS_MPI
1222 <   !! this situation should only arise in MPI simulations
1223 <   if (unique_id_1 == unique_id_2) then
1224 <      skip_it = .true.
1225 <      return
1226 <   end if
1227 <  
1228 <   !! this prevents us from doing the pair on multiple processors
1229 <   if (unique_id_1 < unique_id_2) then
1230 <      if (mod(unique_id_1 + unique_id_2,2) == 0) then
1231 <         skip_it = .true.
1232 <         return
1233 <      endif
1234 <   else                
1235 <      if (mod(unique_id_1 + unique_id_2,2) == 1) then
1236 <         skip_it = .true.
1237 <         return
1238 <      endif
1239 <   endif
1222 >    !! this situation should only arise in MPI simulations
1223 >    if (unique_id_1 == unique_id_2) then
1224 >       skip_it = .true.
1225 >       return
1226 >    end if
1227 >
1228 >    !! this prevents us from doing the pair on multiple processors
1229 >    if (unique_id_1 < unique_id_2) then
1230 >       if (mod(unique_id_1 + unique_id_2,2) == 0) then
1231 >          skip_it = .true.
1232 >          return
1233 >       endif
1234 >    else                
1235 >       if (mod(unique_id_1 + unique_id_2,2) == 1) then
1236 >          skip_it = .true.
1237 >          return
1238 >       endif
1239 >    endif
1240   #endif
1241 <  
1242 <   !! the rest of these situations can happen in all simulations:
1243 <   do i = 1, nExcludes_global      
1244 <      if ((excludesGlobal(i) == unique_id_1) .or. &
1245 <           (excludesGlobal(i) == unique_id_2)) then
1246 <         skip_it = .true.
1247 <         return
1248 <      endif
1249 <   enddo
1250 <  
1251 <   do i = 1, nSkipsForAtom(atom1)
1252 <      if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1253 <         skip_it = .true.
1254 <         return
1255 <      endif
1256 <   end do
1257 <  
1258 <   return
1259 < end function skipThisPair
1260 <
1261 < function FF_UsesDirectionalAtoms() result(doesit)
1262 <   logical :: doesit
1263 <   doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1264 <        FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1265 <        FF_uses_GayBerne .or. FF_uses_Shapes
1266 < end function FF_UsesDirectionalAtoms
1267 <
1268 < function FF_RequiresPrepairCalc() result(doesit)
1269 <   logical :: doesit
1270 <   doesit = FF_uses_EAM
1271 < end function FF_RequiresPrepairCalc
1272 <
1273 < function FF_RequiresPostpairCalc() result(doesit)
1274 <   logical :: doesit
1275 <   doesit = FF_uses_RF
1276 < end function FF_RequiresPostpairCalc
1277 <
1241 >
1242 >    !! the rest of these situations can happen in all simulations:
1243 >    do i = 1, nExcludes_global      
1244 >       if ((excludesGlobal(i) == unique_id_1) .or. &
1245 >            (excludesGlobal(i) == unique_id_2)) then
1246 >          skip_it = .true.
1247 >          return
1248 >       endif
1249 >    enddo
1250 >
1251 >    do i = 1, nSkipsForAtom(atom1)
1252 >       if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1253 >          skip_it = .true.
1254 >          return
1255 >       endif
1256 >    end do
1257 >
1258 >    return
1259 >  end function skipThisPair
1260 >
1261 >  function FF_UsesDirectionalAtoms() result(doesit)
1262 >    logical :: doesit
1263 >    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1264 >         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1265 >         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1266 >  end function FF_UsesDirectionalAtoms
1267 >
1268 >  function FF_RequiresPrepairCalc() result(doesit)
1269 >    logical :: doesit
1270 >    doesit = FF_uses_EAM
1271 >  end function FF_RequiresPrepairCalc
1272 >
1273 >  function FF_RequiresPostpairCalc() result(doesit)
1274 >    logical :: doesit
1275 >    doesit = FF_uses_RF
1276 >  end function FF_RequiresPostpairCalc
1277 >
1278   #ifdef PROFILE
1279 < function getforcetime() result(totalforcetime)
1280 <   real(kind=dp) :: totalforcetime
1281 <   totalforcetime = forcetime
1282 < end function getforcetime
1279 >  function getforcetime() result(totalforcetime)
1280 >    real(kind=dp) :: totalforcetime
1281 >    totalforcetime = forcetime
1282 >  end function getforcetime
1283   #endif
1256
1257 !! This cleans componets of force arrays belonging only to fortran
1284  
1285 < subroutine add_stress_tensor(dpair, fpair)
1286 <  
1287 <   real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1288 <  
1289 <   ! because the d vector is the rj - ri vector, and
1290 <   ! because fx, fy, fz are the force on atom i, we need a
1291 <   ! negative sign here:  
1292 <  
1293 <   tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1294 <   tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1295 <   tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1296 <   tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1297 <   tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1298 <   tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1299 <   tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1300 <   tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1301 <   tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1302 <  
1303 <   virial_Temp = virial_Temp + &
1304 <        (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1305 <  
1306 < end subroutine add_stress_tensor
1307 <
1285 >  !! This cleans componets of force arrays belonging only to fortran
1286 >
1287 >  subroutine add_stress_tensor(dpair, fpair)
1288 >
1289 >    real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1290 >
1291 >    ! because the d vector is the rj - ri vector, and
1292 >    ! because fx, fy, fz are the force on atom i, we need a
1293 >    ! negative sign here:  
1294 >
1295 >    tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1296 >    tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1297 >    tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1298 >    tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1299 >    tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1300 >    tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1301 >    tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1302 >    tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1303 >    tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1304 >
1305 >    virial_Temp = virial_Temp + &
1306 >         (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1307 >
1308 >  end subroutine add_stress_tensor
1309 >
1310   end module doForces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines