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 571 by gezelter, Tue Jul 1 22:39:53 2003 UTC vs.
Revision 1113 by tim, Thu Apr 15 16:18:26 2004 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.16 2003-07-01 22:39:53 gezelter Exp $, $Date: 2003-07-01 22:39:53 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
7 > !! @version $Id: do_Forces.F90,v 1.49 2004-04-15 16:18:26 tim Exp $, $Date: 2004-04-15 16:18:26 $, $Name: not supported by cvs2svn $, $Revision: 1.49 $
8  
9   module do_Forces
10    use force_globals
# Line 15 | Line 15 | module do_Forces
15    use lj
16    use sticky_pair
17    use dipole_dipole
18 +  use charge_charge
19    use reaction_field
20    use gb_pair
21 +  use vector_class
22 +  use eam
23 +  use status
24   #ifdef IS_MPI
25    use mpiSimulation
26   #endif
# Line 27 | Line 31 | module do_Forces
31   #define __FORTRAN90
32   #include "fForceField.h"
33  
34 <  logical, save :: do_forces_initialized = .false.
34 >  logical, save :: haveRlist = .false.
35 >  logical, save :: haveNeighborList = .false.
36 >  logical, save :: havePolicies = .false.
37 >  logical, save :: haveSIMvariables = .false.
38 >  logical, save :: havePropertyMap = .false.
39 >  logical, save :: haveSaneForceField = .false.
40    logical, save :: FF_uses_LJ
41    logical, save :: FF_uses_sticky
42 +  logical, save :: FF_uses_charges
43    logical, save :: FF_uses_dipoles
44    logical, save :: FF_uses_RF
45    logical, save :: FF_uses_GB
46    logical, save :: FF_uses_EAM
47 +  logical, save :: SIM_uses_LJ
48 +  logical, save :: SIM_uses_sticky
49 +  logical, save :: SIM_uses_charges
50 +  logical, save :: SIM_uses_dipoles
51 +  logical, save :: SIM_uses_RF
52 +  logical, save :: SIM_uses_GB
53 +  logical, save :: SIM_uses_EAM
54 +  logical, save :: SIM_requires_postpair_calc
55 +  logical, save :: SIM_requires_prepair_calc
56 +  logical, save :: SIM_uses_directional_atoms
57 +  logical, save :: SIM_uses_PBC
58  
59 +  real(kind=dp), save :: rlist, rlistsq
60 +
61    public :: init_FF
62    public :: do_force_loop
63 +  public :: setRlistDF
64  
65 +
66 + #ifdef PROFILE
67 +  public :: getforcetime
68 +  real, save :: forceTime = 0
69 +  real :: forceTimeInitial, forceTimeFinal
70 +  integer :: nLoops
71 + #endif
72 +
73 +  type :: Properties
74 +     logical :: is_lj     = .false.
75 +     logical :: is_sticky = .false.
76 +     logical :: is_dp     = .false.
77 +     logical :: is_gb     = .false.
78 +     logical :: is_eam    = .false.
79 +     logical :: is_charge = .false.
80 +     real(kind=DP) :: charge = 0.0_DP
81 +     real(kind=DP) :: dipole_moment = 0.0_DP
82 +  end type Properties
83 +
84 +  type(Properties), dimension(:),allocatable :: PropertyMap
85 +
86   contains
87  
88 +  subroutine setRlistDF( this_rlist )
89 +    
90 +    real(kind=dp) :: this_rlist
91 +
92 +    rlist = this_rlist
93 +    rlistsq = rlist * rlist
94 +    
95 +    haveRlist = .true.
96 +
97 +  end subroutine setRlistDF    
98 +
99 +  subroutine createPropertyMap(status)
100 +    integer :: nAtypes
101 +    integer :: status
102 +    integer :: i
103 +    logical :: thisProperty
104 +    real (kind=DP) :: thisDPproperty
105 +
106 +    status = 0
107 +
108 +    nAtypes = getSize(atypes)
109 +
110 +    if (nAtypes == 0) then
111 +       status = -1
112 +       return
113 +    end if
114 +        
115 +    if (.not. allocated(PropertyMap)) then
116 +       allocate(PropertyMap(nAtypes))
117 +    endif
118 +
119 +    do i = 1, nAtypes
120 +       call getElementProperty(atypes, i, "is_LJ", thisProperty)
121 +       PropertyMap(i)%is_LJ = thisProperty
122 +
123 +       call getElementProperty(atypes, i, "is_Charge", thisProperty)
124 +       PropertyMap(i)%is_Charge = thisProperty
125 +      
126 +       if (thisProperty) then
127 +          call getElementProperty(atypes, i, "charge", thisDPproperty)
128 +          PropertyMap(i)%charge = thisDPproperty
129 +       endif
130 +
131 +       call getElementProperty(atypes, i, "is_DP", thisProperty)
132 +       PropertyMap(i)%is_DP = thisProperty
133 +
134 +       if (thisProperty) then
135 +          call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
136 +          PropertyMap(i)%dipole_moment = thisDPproperty
137 +       endif
138 +
139 +       call getElementProperty(atypes, i, "is_Sticky", thisProperty)
140 +       PropertyMap(i)%is_Sticky = thisProperty
141 +       call getElementProperty(atypes, i, "is_GB", thisProperty)
142 +       PropertyMap(i)%is_GB = thisProperty
143 +       call getElementProperty(atypes, i, "is_EAM", thisProperty)
144 +       PropertyMap(i)%is_EAM = thisProperty
145 +    end do
146 +
147 +    havePropertyMap = .true.
148 +
149 +  end subroutine createPropertyMap
150 +
151 +  subroutine setSimVariables()
152 +    SIM_uses_LJ = SimUsesLJ()
153 +    SIM_uses_sticky = SimUsesSticky()
154 +    SIM_uses_charges = SimUsesCharges()
155 +    SIM_uses_dipoles = SimUsesDipoles()
156 +    SIM_uses_RF = SimUsesRF()
157 +    SIM_uses_GB = SimUsesGB()
158 +    SIM_uses_EAM = SimUsesEAM()
159 +    SIM_requires_postpair_calc = SimRequiresPostpairCalc()
160 +    SIM_requires_prepair_calc = SimRequiresPrepairCalc()
161 +    SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
162 +    SIM_uses_PBC = SimUsesPBC()
163 +
164 +    haveSIMvariables = .true.
165 +
166 +    return
167 +  end subroutine setSimVariables
168 +
169 +  subroutine doReadyCheck(error)
170 +    integer, intent(out) :: error
171 +
172 +    integer :: myStatus
173 +
174 +    error = 0
175 +    
176 +    if (.not. havePropertyMap) then
177 +
178 +       myStatus = 0
179 +
180 +       call createPropertyMap(myStatus)
181 +
182 +       if (myStatus .ne. 0) then
183 +          write(default_error, *) 'createPropertyMap failed in do_Forces!'
184 +          error = -1
185 +          return
186 +       endif
187 +    endif
188 +
189 +    if (.not. haveSIMvariables) then
190 +       call setSimVariables()
191 +    endif
192 +
193 +    if (.not. haveRlist) then
194 +       write(default_error, *) 'rList has not been set in do_Forces!'
195 +       error = -1
196 +       return
197 +    endif
198 +
199 +    if (SIM_uses_LJ .and. FF_uses_LJ) then
200 +       if (.not. havePolicies) then
201 +          write(default_error, *) 'LJ mixing Policies have not been set in do_Forces!'
202 +          error = -1
203 +          return
204 +       endif
205 +    endif
206 +
207 +    if (.not. haveNeighborList) then
208 +       write(default_error, *) 'neighbor list has not been initialized in do_Forces!'
209 +       error = -1
210 +       return
211 +    end if
212 +
213 +    if (.not. haveSaneForceField) then
214 +       write(default_error, *) 'Force Field is not sane in do_Forces!'
215 +       error = -1
216 +       return
217 +    end if
218 +
219 + #ifdef IS_MPI
220 +    if (.not. isMPISimSet()) then
221 +       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
222 +       error = -1
223 +       return
224 +    endif
225 + #endif
226 +    return
227 +  end subroutine doReadyCheck
228 +    
229 +
230    subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
231  
232      integer, intent(in) :: LJMIXPOLICY
# Line 64 | Line 251 | contains
251    
252      FF_uses_LJ = .false.
253      FF_uses_sticky = .false.
254 +    FF_uses_charges = .false.
255      FF_uses_dipoles = .false.
256      FF_uses_GB = .false.
257      FF_uses_EAM = .false.
258      
259      call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
260      if (nMatches .gt. 0) FF_uses_LJ = .true.
261 <    
261 >
262 >    call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
263 >    if (nMatches .gt. 0) FF_uses_charges = .true.  
264 >
265      call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
266      if (nMatches .gt. 0) FF_uses_dipoles = .true.
267      
# Line 84 | Line 275 | contains
275      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
276      if (nMatches .gt. 0) FF_uses_EAM = .true.
277      
278 +    !! Assume sanity (for the sake of argument)
279 +    haveSaneForceField = .true.
280 +
281      !! check to make sure the FF_uses_RF setting makes sense
282      
283      if (FF_uses_dipoles) then
90       rrf = getRrf()
91       rt = getRt()      
92       call initialize_dipole(rrf, rt)
284         if (FF_uses_RF) then
285            dielect = getDielect()
286 <          call initialize_rf(rrf, rt, dielect)
286 >          call initialize_rf(dielect)
287         endif
288      else
289         if (FF_uses_RF) then          
290            write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
291            thisStat = -1
292 +          haveSaneForceField = .false.
293            return
294         endif
295 <    endif
295 >    endif
296  
297      if (FF_uses_LJ) then
298        
107       call getRcut(rcut)
108
299         select case (LJMIXPOLICY)
300         case (LB_MIXING_RULE)
301 <          call init_lj_FF(LB_MIXING_RULE, rcut, my_status)            
301 >          call init_lj_FF(LB_MIXING_RULE, my_status)            
302         case (EXPLICIT_MIXING_RULE)
303 <          call init_lj_FF(EXPLICIT_MIXING_RULE, rcut, my_status)
303 >          call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
304         case default
305            write(default_error,*) 'unknown LJ Mixing Policy!'
306            thisStat = -1
307 +          haveSaneForceField = .false.
308            return            
309         end select
310         if (my_status /= 0) then
311            thisStat = -1
312 +          haveSaneForceField = .false.
313            return
314         end if
315 +       havePolicies = .true.
316      endif
317  
318      if (FF_uses_sticky) then
319         call check_sticky_FF(my_status)
320         if (my_status /= 0) then
321            thisStat = -1
322 +          haveSaneForceField = .false.
323            return
324         end if
325      endif
326 <    
326 >
327 >
328 >    if (FF_uses_EAM) then
329 >         call init_EAM_FF(my_status)
330 >       if (my_status /= 0) then
331 >          write(default_error, *) "init_EAM_FF returned a bad status"
332 >          thisStat = -1
333 >          haveSaneForceField = .false.
334 >          return
335 >       end if
336 >    endif
337 >
338      if (FF_uses_GB) then
339         call check_gb_pair_FF(my_status)
340         if (my_status .ne. 0) then
341            thisStat = -1
342 +          haveSaneForceField = .false.
343            return
344         endif
345      endif
346  
347      if (FF_uses_GB .and. FF_uses_LJ) then
348      endif
349 <    if (.not. do_forces_initialized) then
349 >    if (.not. haveNeighborList) then
350         !! Create neighbor lists
351 <       call expandNeighborList(getNlocal(), my_status)
351 >       call expandNeighborList(nLocal, my_status)
352         if (my_Status /= 0) then
353            write(default_error,*) "SimSetup: ExpandNeighborList returned error."
354            thisStat = -1
355            return
356         endif
357 +       haveNeighborList = .true.
358      endif
359 <
153 <    do_forces_initialized = .true.    
154 <
359 >    
360    end subroutine init_FF
361    
362  
# Line 160 | Line 365 | contains
365    subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
366         error)
367      !! Position array provided by C, dimensioned by getNlocal
368 <    real ( kind = dp ), dimension(3,getNlocal()) :: q
368 >    real ( kind = dp ), dimension(3,nLocal) :: q
369      !! Rotation Matrix for each long range particle in simulation.
370 <    real( kind = dp), dimension(9,getNlocal()) :: A    
370 >    real( kind = dp), dimension(9,nLocal) :: A    
371      !! Unit vectors for dipoles (lab frame)
372 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
372 >    real( kind = dp ), dimension(3,nLocal) :: u_l
373      !! Force array provided by C, dimensioned by getNlocal
374 <    real ( kind = dp ), dimension(3,getNlocal()) :: f
374 >    real ( kind = dp ), dimension(3,nLocal) :: f
375      !! Torsion array provided by C, dimensioned by getNlocal
376 <    real( kind = dp ), dimension(3,getNlocal()) :: t    
376 >    real( kind = dp ), dimension(3,nLocal) :: t    
377 >
378      !! Stress Tensor
379      real( kind = dp), dimension(9) :: tau  
380      real ( kind = dp ) :: pot
# Line 179 | Line 385 | contains
385      real( kind = DP ) :: pot_local
386      integer :: nrow
387      integer :: ncol
388 +    integer :: nprocs
389   #endif
183    integer :: nlocal
390      integer :: natoms    
391      logical :: update_nlist  
392      integer :: i, j, jbeg, jend, jnab
393      integer :: nlist
394 <    real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
394 >    real( kind = DP ) ::  rijsq
395      real(kind=dp),dimension(3) :: d
396      real(kind=dp) :: rfpot, mu_i, virial
397 <    integer :: me_i
397 >    integer :: me_i, me_j
398      logical :: is_dp_i
399      integer :: neighborListSize
400      integer :: listerror, error
401      integer :: localError
402 +    integer :: propPack_i, propPack_j
403  
404 +    real(kind=dp) :: listSkin = 1.0  
405 +
406      !! initialize local variables  
407  
408   #ifdef IS_MPI
409      pot_local = 0.0_dp
201    nlocal = getNlocal()
410      nrow   = getNrow(plan_row)
411      ncol   = getNcol(plan_col)
412   #else
205    nlocal = getNlocal()
413      natoms = nlocal
414   #endif
415 <  
416 <    call getRcut(rcut,rc2=rcutsq)
210 <    call getRlist(rlist,rlistsq)
211 <    
212 <    call check_initialization(localError)
415 >
416 >    call doReadyCheck(localError)
417      if ( localError .ne. 0 ) then
418 +       call handleError("do_force_loop", "Not Initialized")
419         error = -1
420         return
421      end if
# Line 226 | Line 431 | contains
431      call gather(q,q_Row,plan_row3d)
432      call gather(q,q_Col,plan_col3d)
433          
434 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
434 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
435         call gather(u_l,u_l_Row,plan_row3d)
436         call gather(u_l,u_l_Col,plan_col3d)
437        
# Line 235 | Line 440 | contains
440      endif
441      
442   #endif
443 <    
444 <    if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
443 >
444 > !! Begin force loop timing:
445 > #ifdef PROFILE
446 >    call cpu_time(forceTimeInitial)
447 >    nloops = nloops + 1
448 > #endif
449 >  
450 >    if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
451         !! See if we need to update neighbor lists
452 <       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
452 >       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
453         !! if_mpi_gather_stuff_for_prepair
454         !! do_prepair_loop_if_needed
455         !! if_mpi_scatter_stuff_from_prepair
456         !! if_mpi_gather_stuff_from_prepair_to_main_loop
457 <    else
458 <       !! See if we need to update neighbor lists
459 <       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
457 >    
458 > !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
459 > #ifdef IS_MPI
460 >    
461 >    if (update_nlist) then
462 >      
463 >       !! save current configuration, construct neighbor list,
464 >       !! and calculate forces
465 >       call saveNeighborList(nlocal, q)
466 >      
467 >       neighborListSize = size(list)
468 >       nlist = 0      
469 >      
470 >       do i = 1, nrow
471 >          point(i) = nlist + 1
472 >          
473 >          prepair_inner: do j = 1, ncol
474 >            
475 >             if (skipThisPair(i,j)) cycle prepair_inner
476 >            
477 >             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
478 >            
479 >             if (rijsq < rlistsq) then            
480 >                
481 >                nlist = nlist + 1
482 >                
483 >                if (nlist > neighborListSize) then
484 >                   call expandNeighborList(nlocal, listerror)
485 >                   if (listerror /= 0) then
486 >                      error = -1
487 >                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
488 >                      return
489 >                   end if
490 >                   neighborListSize = size(list)
491 >                endif
492 >                
493 >                list(nlist) = j
494 >                call do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot_local)                      
495 >             endif
496 >          enddo prepair_inner
497 >       enddo
498 >
499 >       point(nrow + 1) = nlist + 1
500 >      
501 >    else  !! (of update_check)
502 >
503 >       ! use the list to find the neighbors
504 >       do i = 1, nrow
505 >          JBEG = POINT(i)
506 >          JEND = POINT(i+1) - 1
507 >          ! check thiat molecule i has neighbors
508 >          if (jbeg .le. jend) then
509 >            
510 >             do jnab = jbeg, jend
511 >                j = list(jnab)
512 >
513 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
514 >                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
515 >                     u_l, A, f, t, pot_local)
516 >
517 >             enddo
518 >          endif
519 >       enddo
520      endif
521      
522 < #ifdef IS_MPI
522 > #else
523      
524      if (update_nlist) then
525        
526 +       ! save current configuration, contruct neighbor list,
527 +       ! and calculate forces
528 +       call saveNeighborList(natoms, q)
529 +      
530 +       neighborListSize = size(list)
531 +  
532 +       nlist = 0
533 +
534 +       do i = 1, natoms-1
535 +          point(i) = nlist + 1
536 +          
537 +          prepair_inner: do j = i+1, natoms
538 +            
539 +             if (skipThisPair(i,j))  cycle prepair_inner
540 +                          
541 +             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
542 +          
543 +
544 +             if (rijsq < rlistsq) then
545 +
546 +          
547 +                nlist = nlist + 1
548 +              
549 +                if (nlist > neighborListSize) then
550 +                   call expandNeighborList(natoms, listerror)
551 +                   if (listerror /= 0) then
552 +                      error = -1
553 +                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
554 +                      return
555 +                   end if
556 +                   neighborListSize = size(list)
557 +                endif
558 +                
559 +                list(nlist) = j
560 +                
561 +                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
562 +                        u_l, A, f, t, pot)
563 +                
564 +             endif
565 +          enddo prepair_inner
566 +       enddo
567 +      
568 +       point(natoms) = nlist + 1
569 +      
570 +    else !! (update)
571 +  
572 +       ! use the list to find the neighbors
573 +       do i = 1, natoms-1
574 +          JBEG = POINT(i)
575 +          JEND = POINT(i+1) - 1
576 +          ! check thiat molecule i has neighbors
577 +          if (jbeg .le. jend) then
578 +            
579 +             do jnab = jbeg, jend
580 +                j = list(jnab)
581 +
582 +                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
583 +                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
584 +                     u_l, A, f, t, pot)
585 +
586 +             enddo
587 +          endif
588 +       enddo
589 +    endif    
590 + #endif
591 +    !! Do rest of preforce calculations
592 +    !! do necessary preforce calculations  
593 +    call do_preforce(nlocal,pot)
594 +   ! we have already updated the neighbor list set it to false...
595 +   update_nlist = .false.
596 +    else
597 +       !! See if we need to update neighbor lists for non pre-pair
598 +       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
599 +    endif
600 +
601 +
602 +
603 +
604 +
605 + !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>>>>>>>>>>>>>>>>
606 +
607 +
608 +
609 +
610 +  
611 + #ifdef IS_MPI
612 +    
613 +    if (update_nlist) then
614         !! save current configuration, construct neighbor list,
615         !! and calculate forces
616         call saveNeighborList(nlocal, q)
# Line 260 | Line 619 | contains
619         nlist = 0      
620        
621         do i = 1, nrow
622 +
623            point(i) = nlist + 1
624            
625            inner: do j = 1, ncol
# Line 268 | Line 628 | contains
628              
629               call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
630              
631 <             if (rijsq <  rlistsq) then            
631 >             if (rijsq < rlistsq) then            
632                  
633                  nlist = nlist + 1
634                  
# Line 284 | Line 644 | contains
644                  
645                  list(nlist) = j
646                                  
647 <                if (rijsq <  rcutsq) then
648 <                   call do_pair(i, j, rijsq, d, do_pot, do_stress, &
649 <                        u_l, A, f, t, pot_local)
290 <                endif
647 >                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
648 >                     u_l, A, f, t, pot_local)
649 >                
650               endif
651            enddo inner
652         enddo
# Line 318 | Line 677 | contains
677   #else
678      
679      if (update_nlist) then
680 <      
680 >
681         ! save current configuration, contruct neighbor list,
682         ! and calculate forces
683         call saveNeighborList(natoms, q)
# Line 337 | Line 696 | contains
696               call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
697            
698  
699 <             if (rijsq <  rlistsq) then
699 >             if (rijsq < rlistsq) then
700                  
701                  nlist = nlist + 1
702                
# Line 353 | Line 712 | contains
712                  
713                  list(nlist) = j
714                  
715 <                if (rijsq <  rcutsq) then
357 <                   call do_pair(i, j, rijsq, d, do_pot, do_stress, &
715 >                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
716                          u_l, A, f, t, pot)
717 <                endif
717 >                
718               endif
719            enddo inner
720         enddo
# Line 387 | Line 745 | contains
745   #endif
746      
747      ! phew, done with main loop.
748 <    
748 >
749 > !! Do timing
750 > #ifdef PROFILE
751 >    call cpu_time(forceTimeFinal)
752 >    forceTime = forceTime + forceTimeFinal - forceTimeInitial
753 > #endif
754 >
755 >
756   #ifdef IS_MPI
757      !!distribute forces
758    
# Line 403 | Line 768 | contains
768         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
769      end do
770      
771 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
771 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
772         t_temp = 0.0_dp
773         call scatter(t_Row,t_temp,plan_row3d)
774         do i = 1,nlocal
# Line 437 | Line 802 | contains
802      endif    
803   #endif
804  
805 <    if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
805 >    if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
806        
807 <       if (FF_uses_RF .and. SimUsesRF()) then
808 <          
807 >       if (FF_uses_RF .and. SIM_uses_RF) then
808 >
809   #ifdef IS_MPI
810            call scatter(rf_Row,rf,plan_row3d)
811            call scatter(rf_Col,rf_Temp,plan_col3d)
# Line 449 | Line 814 | contains
814            end do
815   #endif
816            
817 <          do i = 1, getNlocal()
817 >          do i = 1, nLocal
818  
819               rfpot = 0.0_DP
820   #ifdef IS_MPI
# Line 457 | Line 822 | contains
822   #else
823               me_i = atid(i)
824   #endif
825 <             call getElementProperty(atypes, me_i, "is_DP", is_DP_i)      
826 <             if ( is_DP_i ) then
827 <                call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
825 >
826 >             if (PropertyMap(me_i)%is_DP) then
827 >
828 >                mu_i = PropertyMap(me_i)%dipole_moment
829 >
830                  !! The reaction field needs to include a self contribution
831                  !! to the field:
832 <                call accumulate_self_rf(i, mu_i, u_l)            
832 >                call accumulate_self_rf(i, mu_i, u_l)
833                  !! Get the reaction field contribution to the
834                  !! potential and torques:
835                  call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
# Line 499 | Line 866 | contains
866         tau = tau_Temp
867         virial = virial_Temp
868      endif
869 <
869 >    
870   #endif
871      
872 +    
873 +    
874    end subroutine do_force_loop
875  
876    subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
877  
878      real( kind = dp ) :: pot
879 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
880 <    real (kind=dp), dimension(9,getNlocal()) :: A
881 <    real (kind=dp), dimension(3,getNlocal()) :: f
882 <    real (kind=dp), dimension(3,getNlocal()) :: t
879 >    real( kind = dp ), dimension(3,nLocal) :: u_l
880 >    real (kind=dp), dimension(9,nLocal) :: A
881 >    real (kind=dp), dimension(3,nLocal) :: f
882 >    real (kind=dp), dimension(3,nLocal) :: t
883  
884      logical, intent(inout) :: do_pot, do_stress
885      integer, intent(in) :: i, j
886      real ( kind = dp ), intent(inout)    :: rijsq
887      real ( kind = dp )                :: r
888      real ( kind = dp ), intent(inout) :: d(3)
520    logical :: is_LJ_i, is_LJ_j
521    logical :: is_DP_i, is_DP_j
522    logical :: is_GB_i, is_GB_j
523    logical :: is_Sticky_i, is_Sticky_j
889      integer :: me_i, me_j
890  
891      r = sqrt(rijsq)
892  
528
529
893   #ifdef IS_MPI
894      if (tagRow(i) .eq. tagColumn(j)) then
895         write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
896      endif
534
897      me_i = atid_row(i)
898      me_j = atid_col(j)
537
899   #else
539
900      me_i = atid(i)
901      me_j = atid(j)
542
902   #endif
903 <
904 <    if (FF_uses_LJ .and. SimUsesLJ()) then
546 <       call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
547 <       call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
548 <
549 <       if ( is_LJ_i .and. is_LJ_j ) &
550 <            call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
551 <    endif
552 <
553 <    if (FF_uses_dipoles .and. SimUsesDipoles()) then
554 <       call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
555 <       call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
903 >    
904 >    if (FF_uses_LJ .and. SIM_uses_LJ) then
905        
906 <       if ( is_DP_i .and. is_DP_j ) then
907 <          
906 >       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
907 >          call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
908 >       endif
909 >      
910 >    endif
911 >    
912 >    if (FF_uses_charges .and. SIM_uses_charges) then
913 >      
914 >       if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
915 >          call do_charge_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
916 >       endif
917 >      
918 >    endif
919 >    
920 >    if (FF_uses_dipoles .and. SIM_uses_dipoles) then
921 >      
922 >       if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
923            call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
924                 do_pot, do_stress)
925 <          if (FF_uses_RF .and. SimUsesRF()) then
925 >          if (FF_uses_RF .and. SIM_uses_RF) then
926               call accumulate_rf(i, j, r, u_l)
927               call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
928 <          endif
565 <          
928 >          endif          
929         endif
930 +
931      endif
932  
933 <    if (FF_uses_Sticky .and. SimUsesSticky()) then
933 >    if (FF_uses_Sticky .and. SIM_uses_sticky) then
934  
935 <       call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
572 <       call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
573 <
574 <       if ( is_Sticky_i .and. is_Sticky_j ) then
935 >       if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
936            call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
937                 do_pot, do_stress)
938         endif
939 +
940      endif
941  
942  
943 <    if (FF_uses_GB .and. SimUsesGB()) then
582 <
583 <       call getElementProperty(atypes, me_i, "is_GB", is_GB_i)
584 <       call getElementProperty(atypes, me_j, "is_GB", is_GB_j)
943 >    if (FF_uses_GB .and. SIM_uses_GB) then
944        
945 <       if ( is_GB_i .and. is_GB_j ) then
945 >       if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
946            call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
947                 do_pot, do_stress)          
948         endif
949 +
950      endif
951 <    
951 >      
952 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
953 >      
954 >       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
955 >          call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
956 >       endif
957 >      
958 >    endif
959 >
960    end subroutine do_pair
961 +
962 +
963 +
964 +  subroutine do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
965 +   real( kind = dp ) :: pot
966 +   real( kind = dp ), dimension(3,nLocal) :: u_l
967 +   real (kind=dp), dimension(9,nLocal) :: A
968 +   real (kind=dp), dimension(3,nLocal) :: f
969 +   real (kind=dp), dimension(3,nLocal) :: t
970 +  
971 +   logical, intent(inout) :: do_pot, do_stress
972 +   integer, intent(in) :: i, j
973 +   real ( kind = dp ), intent(inout)    :: rijsq
974 +   real ( kind = dp )                :: r
975 +   real ( kind = dp ), intent(inout) :: d(3)
976 +  
977 +   logical :: is_EAM_i, is_EAM_j
978 +  
979 +   integer :: me_i, me_j
980 +  
981 +   r = sqrt(rijsq)
982 +  
983 +
984 + #ifdef IS_MPI
985 +   if (tagRow(i) .eq. tagColumn(j)) then
986 +      write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
987 +   endif
988 +  
989 +   me_i = atid_row(i)
990 +   me_j = atid_col(j)
991 +  
992 + #else
993 +  
994 +   me_i = atid(i)
995 +   me_j = atid(j)
996 +  
997 + #endif
998 +    
999 +   if (FF_uses_EAM .and. SIM_uses_EAM) then
1000  
1001 +      if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1002 +           call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1003  
1004 +   endif
1005 +  
1006 + end subroutine do_prepair
1007 +
1008 +
1009 +
1010 +
1011 +  subroutine do_preforce(nlocal,pot)
1012 +    integer :: nlocal
1013 +    real( kind = dp ) :: pot
1014 +
1015 +    if (FF_uses_EAM .and. SIM_uses_EAM) then
1016 +       call calc_EAM_preforce_Frho(nlocal,pot)
1017 +    endif
1018 +
1019 +
1020 +  end subroutine do_preforce
1021 +  
1022 +  
1023    subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1024      
1025      real (kind = dp), dimension(3) :: q_i
# Line 603 | Line 1031 | contains
1031      d(1:3) = q_j(1:3) - q_i(1:3)
1032  
1033      ! Wrap back into periodic box if necessary
1034 <    if ( SimUsesPBC() ) then
1034 >    if ( SIM_uses_PBC ) then
1035        
1036         if( .not.boxIsOrthorhombic ) then
1037            ! calc the scaled coordinates.
1038            
1039 <          scaled = matmul(d, HmatInv)
1039 >          scaled = matmul(HmatInv, d)
1040            
1041            ! wrap the scaled coordinates
1042  
1043 <          do i = 1, 3
1044 <             scaled(i) = scaled(i) - anint(scaled(i))
617 <          enddo
1043 >          scaled = scaled  - anint(scaled)
1044 >          
1045  
1046            ! calc the wrapped real coordinates from the wrapped scaled
1047            ! coordinates
1048  
1049 <          d = matmul(scaled,Hmat)
1049 >          d = matmul(Hmat,scaled)
1050  
1051         else
1052            ! calc the scaled coordinates.
# Line 644 | Line 1071 | contains
1071      
1072    end subroutine get_interatomic_vector
1073    
647  subroutine check_initialization(error)
648    integer, intent(out) :: error
649    
650    error = 0
651    ! Make sure we are properly initialized.
652    if (.not. do_forces_initialized) then
653       error = -1
654       return
655    endif
656
657 #ifdef IS_MPI
658    if (.not. isMPISimSet()) then
659       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
660       error = -1
661       return
662    endif
663 #endif
664    
665    return
666  end subroutine check_initialization
667
668  
1074    subroutine zero_work_arrays()
1075      
1076   #ifdef IS_MPI
# Line 697 | Line 1102 | contains
1102  
1103   #endif
1104  
1105 +
1106 +    if (FF_uses_EAM .and. SIM_uses_EAM) then
1107 +       call clean_EAM()
1108 +    endif
1109 +
1110 +
1111 +
1112 +
1113 +
1114      rf = 0.0_dp
1115      tau_Temp = 0.0_dp
1116      virial_Temp = 0.0_dp
# Line 809 | Line 1223 | end module do_Forces
1223      doesit = FF_uses_RF
1224    end function FF_RequiresPostpairCalc
1225    
1226 + #ifdef PROFILE
1227 +  function getforcetime() result(totalforcetime)
1228 +    real(kind=dp) :: totalforcetime
1229 +    totalforcetime = forcetime
1230 +  end function getforcetime
1231 + #endif
1232 +
1233 + !! This cleans componets of force arrays belonging only to fortran
1234 +
1235   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines