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 297 by gezelter, Thu Mar 6 22:08:29 2003 UTC vs.
Revision 312 by gezelter, Tue Mar 11 17:46:18 2003 UTC

# Line 1 | Line 1
1 + !! do_Forces.F90
2 + !! module do_Forces
3   !! Calculates Long Range forces.
4 +
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.4 2003-03-06 22:08:29 gezelter Exp $, $Date: 2003-03-06 22:08:29 $, $Name: not supported by cvs2svn $, $Revision: 1.4 $
7 > !! @version $Id: do_Forces.F90,v 1.10 2003-03-11 17:46:18 gezelter Exp $, $Date: 2003-03-11 17:46:18 $, $Name: not supported by cvs2svn $, $Revision: 1.10 $
8  
9  
10  
11   module do_Forces
12    use simulation
13    use definitions
14 <  use generic_atypes
14 >  use forceGlobals
15 >  use atype_typedefs
16    use neighborLists
17 +
18    
19 <  use lj_FF
19 >  use lj
20    use sticky_FF
21 <  use dp_FF
21 >  use dipole_dipole
22    use gb_FF
23  
24   #ifdef IS_MPI
# Line 22 | Line 27 | module do_Forces
27    implicit none
28    PRIVATE
29  
30 < !! Number of lj_atypes in lj_atype_list
26 <  integer, save :: n_atypes = 0
30 > public :: do_force_loop
31  
28 !! Global list of lj atypes in simulation
29  type (atype), pointer :: ListHead => null()
30  type (atype), pointer :: ListTail => null()
31
32
33
34
35  logical, save :: firstTime = .True.
36
37 !! Atype identity pointer lists
38 #ifdef IS_MPI
39 !! Row lj_atype pointer list
40  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
41 !! Column lj_atype pointer list
42  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
43 #else
44  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
45 #endif
46
47
48 !! Logical has lj force field module been initialized?
49  logical, save :: isFFinit = .false.
50
51 !! Use periodic boundry conditions
52  logical :: wrap = .false.
53
54 !! Potential energy global module variables
55 #ifdef IS_MPI
56  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
57  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
58
59  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
60  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
61
62  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
63  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
64
65  real(kind = dp), dimension(9,getNrow(plan_row)) :: ARow = 0.0_dp
66  real(kind = dp), dimension(9,getNcol(plan_col)) :: ACol = 0.0_dp  
67
68  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
69  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
70  real(kind = dp), dimension(3,getNlocal()) :: fTemp1 = 0.0_dp
71  real(kind = dp), dimension(3,getNlocal()) :: tTemp1 = 0.0_dp
72  real(kind = dp), dimension(3,getNlocal()) :: fTemp2 = 0.0_dp
73  real(kind = dp), dimension(3,getNlocal()) :: tTemp2 = 0.0_dp
74  real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
75  real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
76
77  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
78  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
79
80  real(kind = dp), dimension(3,getNrow(plan_row)) :: rflRow = 0.0_dp
81  real(kind = dp), dimension(3,getNcol(plan_col)) :: rflCol = 0.0_dp
82  real(kind = dp), dimension(3,getNlocal()) :: rflTemp = 0.0_dp
83
84  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
85  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
86
87  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
88 #endif
89  real(kind = dp) :: pe = 0.0_dp
90  real(kind = dp), dimension(3,natoms) :: fTemp = 0.0_dp
91  real(kind = dp), dimension(3,natoms) :: tTemp = 0.0_dp
92  real(kind = dp), dimension(3,natoms) :: rflTemp = 0.0_dp
93  real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
94
95  logical :: do_preForce  = .false.
96  logical :: do_postForce = .false.
97
98
99
100 !! Public methods and data
101  public :: new_atype
102  public :: do_forceLoop
103  public :: init_FF
104
105  
106
107
32   contains
109
110 !! Adds a new lj_atype to the list.
111  subroutine new_atype(ident,mass,epsilon,sigma, &
112       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
113    real( kind = dp ), intent(in) :: mass
114    real( kind = dp ), intent(in) :: epsilon
115    real( kind = dp ), intent(in) :: sigma
116    real( kind = dp ), intent(in) :: w0
117    real( kind = dp ), intent(in) :: v0
118    real( kind = dp ), intent(in) :: dipoleMoment
119
120    integer, intent(in) :: ident
121    integer, intent(out) :: status
122    integer, intent(in) :: is_Sticky
123    integer, intent(in) :: is_DP
124    integer, intent(in) :: is_GB
125    integer, intent(in) :: is_LJ
126
127
128    type (atype), pointer :: the_new_atype
129    integer :: alloc_error
130    integer :: atype_counter = 0
131    integer :: alloc_size
132    integer :: err_stat
133    status = 0
134
135
136
137 ! allocate a new atype    
138    allocate(the_new_atype,stat=alloc_error)
139    if (alloc_error /= 0 ) then
140       status = -1
141       return
142    end if
143
144 ! assign our new atype information
145    the_new_atype%mass        = mass
146    the_new_atype%epsilon     = epsilon
147    the_new_atype%sigma       = sigma
148    the_new_atype%sigma2      = sigma * sigma
149    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
150         * the_new_atype%sigma2
151    the_new_atype%w0       = w0
152    the_new_atype%v0       = v0
153    the_new_atype%dipoleMoment       = dipoleMoment
154
155    
156 ! assume that this atype will be successfully added
157    the_new_atype%atype_ident = ident
158    the_new_atype%atype_number = n_lj_atypes + 1
159    
160    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
161    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
162    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
163    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
164
165    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
166    if (err_stat /= 0 ) then
167       status = -1
168       return
169    endif
170
171    n_atypes = n_atypes + 1
172
173
174  end subroutine new_atype
175
176
177  subroutine init_FF(nComponents,ident, status)
178 !! Number of components in ident array
179    integer, intent(inout) :: nComponents
180 !! Array of identities nComponents long corresponding to
181 !! ljatype ident.
182    integer, dimension(nComponents),intent(inout) :: ident
183 !!  Result status, success = 0, error = -1
184    integer, intent(out) :: Status
185
186    integer :: alloc_stat
187
188    integer :: thisStat
189    integer :: i
190
191    integer :: myNode
192 #ifdef IS_MPI
193    integer, allocatable, dimension(:) :: identRow
194    integer, allocatable, dimension(:) :: identCol
195    integer :: nrow
196    integer :: ncol
197 #endif
198    status = 0
199  
200
201    
202
203 !! if were're not in MPI, we just update ljatypePtrList
204 #ifndef IS_MPI
205    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
206    if ( thisStat /= 0 ) then
207       status = -1
208       return
209    endif
210
211    
212 ! if were're in MPI, we also have to worry about row and col lists    
213 #else
214  
215 ! We can only set up forces if mpiSimulation has been setup.
216    if (.not. isMPISimSet()) then
217       write(default_error,*) "MPI is not set"
218       status = -1
219       return
220    endif
221    nrow = getNrow(plan_row)
222    ncol = getNcol(plan_col)
223    mynode = getMyNode()
224 !! Allocate temperary arrays to hold gather information
225    allocate(identRow(nrow),stat=alloc_stat)
226    if (alloc_stat /= 0 ) then
227       status = -1
228       return
229    endif
230
231    allocate(identCol(ncol),stat=alloc_stat)
232    if (alloc_stat /= 0 ) then
233       status = -1
234       return
235    endif
236
237 !! Gather idents into row and column idents
238
239    call gather(ident,identRow,plan_row)
240    call gather(ident,identCol,plan_col)
241    
242  
243 !! Create row and col pointer lists
244  
245    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
246    if (thisStat /= 0 ) then
247       status = -1
248       return
249    endif
250  
251    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
252    if (thisStat /= 0 ) then
253       status = -1
254       return
255    endif
256
257 !! free temporary ident arrays
258    if (allocated(identCol)) then
259       deallocate(identCol)
260    end if
261    if (allocated(identCol)) then
262       deallocate(identRow)
263    endif
264
265 #endif
266    
267    call initForce_Modules(thisStat)
268    if (thisStat /= 0) then
269       status = -1
270       return
271    endif
272
273 !! Create neighbor lists
274    call expandList(thisStat)
275    if (thisStat /= 0) then
276       status = -1
277       return
278    endif
279
280    isFFinit = .true.
281
282
283  end subroutine init_FF
33  
34 <
286 <
287 <
288 <  subroutine initForce_Modules(thisStat)
289 <    integer, intent(out) :: thisStat
290 <    integer :: my_status
291 <    
292 <    thisStat = 0
293 <    call init_lj_FF(ListHead,my_status)
294 <    if (my_status /= 0) then
295 <       thisStat = -1
296 <       return
297 <    end if
298 <
299 <  end subroutine initForce_Modules
300 <
301 <
302 <
303 <
304 < !! FORCE routine Calculates Lennard Jones forces.
34 > !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
35   !------------------------------------------------------------->
36    subroutine do_force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
37   !! Position array provided by C, dimensioned by getNlocal
# Line 356 | Line 86 | contains
86    real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
87    real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
88  
89 <  real( kind = DP ) :: dielectric = 0.0_dp
89 >  
90  
91   ! a rig that need to be fixed.
92   #ifdef IS_MPI
# Line 414 | Line 144 | contains
144  
145   ! communicate MPI positions
146   #ifdef IS_MPI    
147 <    call gather(q,qRow,plan_row3d)
148 <    call gather(q,qCol,plan_col3d)
147 >    call gather(q,q_Row,plan_row3d)
148 >    call gather(q,q_Col,plan_col3d)
149  
150 <    call gather(mu,muRow,plan_row3d)
151 <    call gather(mu,muCol,plan_col3d)
150 >    call gather(u_l,u_l_Row,plan_row3d)
151 >    call gather(u_l,u_l_Col,plan_col3d)
152  
153 <    call gather(u_l,u_lRow,plan_row3d)
154 <    call gather(u_l,u_lCol,plan_col3d)
425 <
426 <    call gather(A,ARow,plan_row_rotation)
427 <    call gather(A,ACol,plan_col_rotation)
153 >    call gather(A,A_Row,plan_row_rotation)
154 >    call gather(A,A_Col,plan_col_rotation)
155   #endif
156  
157  
# Line 450 | Line 177 | contains
177            inner: do j = 1, ncol
178               Atype_j => identPtrListColumn(j)%this
179              
180 <             call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
180 >             call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
181                    rxij,ryij,rzij,rijsq,r)
182              
183               ! skip the loop if the atoms are identical
# Line 494 | Line 221 | contains
221               do jnab = jbeg, jend
222                  j = list(jnab)
223                  Atype_j = identPtrListColumn(j)%this
224 <                call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
224 >                call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
225                       rxij,ryij,rzij,rijsq,r)
226                  
227                  call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
# Line 604 | Line 331 | contains
331   #endif
332  
333  
607
608
334   #ifdef IS_MPI
335      !!distribute forces
336  
337 <    call scatter(fRow,fTemp1,plan_row3d)
338 <    call scatter(fCol,fTemp2,plan_col3d)
614 <
615 <
337 >    call scatter(f_Row,f,plan_row3d)
338 >    call scatter(f_Col,f_temp,plan_col3d)
339      do i = 1,nlocal
340 <       fTemp(1:3,i) = fTemp1(1:3,i) + fTemp2(1:3,i)
340 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
341      end do
342  
343 <    if (do_torque) then
344 <       call scatter(tRow,tTemp1,plan_row3d)
345 <       call scatter(tCol,tTemp2,plan_col3d)
343 >    if (doTorque()) then
344 >       call scatter(t_Row,t,plan_row3d)
345 >       call scatter(t_Col,t_temp,plan_col3d)
346      
347         do i = 1,nlocal
348 <          tTemp(1:3,i) = tTemp1(1:3,i) + tTemp2(1:3,i)
348 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
349         end do
350      endif
351 <
351 >    
352      if (do_pot) then
353         ! scatter/gather pot_row into the members of my column
354 <       call scatter(eRow,eTemp,plan_row)
354 >       call scatter(pot_Row, pot_Temp, plan_row)
355        
356         ! scatter/gather pot_local into all other procs
357         ! add resultant to get total pot
358         do i = 1, nlocal
359 <          pe_local = pe_local + eTemp(i)
359 >          pot_local = pot_local + pot_Temp(i)
360         enddo
361  
362 <       eTemp = 0.0E0_DP
363 <       call scatter(eCol,eTemp,plan_col)
362 >       pot_Temp = 0.0_DP
363 >
364 >       call scatter(pot_Col, pot_Temp, plan_col)
365         do i = 1, nlocal
366 <          pe_local = pe_local + eTemp(i)
366 >          pot_local = pot_local + pot_Temp(i)
367         enddo
368        
369 <       pe = pe_local
369 >       pot = pot_local
370      endif
647 #else
648 ! Copy local array into return array for c
649    f = f+fTemp
650    t = t+tTemp
651 #endif
371  
372 <    potE = pe
372 >    if (doStress()) then
373 >       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
374 >            mpi_comm_world,mpi_err)
375 >       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
376 >            mpi_comm_world,mpi_err)
377 >    endif
378  
379 + #endif
380  
381 <    if (do_stress) then
382 < #ifdef IS_MPI
383 <       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
659 <            mpi_comm_world,mpi_err)
660 < #else
661 <       tau = tauTemp
662 < #endif      
381 >    if (doStress()) then
382 >       tau = tau_Temp
383 >       virial = virial_Temp
384      endif
385  
386    end subroutine do_force_loop
387  
388  
668
669
670
671
672
673
674
675
389   !! Calculate any pre-force loop components and update nlist if necessary.
390    subroutine do_preForce(updateNlist)
391      logical, intent(inout) :: updateNlist
# Line 735 | Line 448 | contains
448      real( kind = dp ) ::  drdz = 0.0_dp
449      
450  
451 + #ifdef IS_MPI
452 +
453      if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
454 <       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
454 >       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
455 >            pot, f)
456      endif
457  
458      if (Atype_i%is_dp .and. Atype_j%is_dp) then
459  
460 < #ifdef IS_MPI
461 <       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
746 <            ulRow(:,i), ulCol(:,j), rt, rrf, pot)
747 < #else
748 <       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
749 <            ul(:,i), ul(:,j), rt, rrf, pot)
750 < #endif
460 >       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
461 >            pot, u_l, f, t)
462  
463         if (do_reaction_field) then
464 < #ifdef IS_MPI
754 <          call accumulate_rf(i, j, r_ij, rflRow(:,i), rflCol(:j), &
755 <               ulRow(:i), ulCol(:,j), rt, rrf)
756 < #else
757 <          call accumulate_rf(i, j, r_ij, rfl(:,i), rfl(:j), &
758 <               ul(:,i), ul(:,j), rt, rrf)
759 < #endif
464 >          call accumulate_rf(i, j, r_ij, rt, rrf)
465         endif
466  
467 +    endif
468  
763    endif
764
469      if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
470 <       call getstickyforce(r,pot,dudr,ljAtype_i,ljAtype_j)
470 >       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
471      endif
472  
769      
770 #ifdef IS_MPI
771                eRow(i) = eRow(i) + pot*0.5
772                eCol(i) = eCol(i) + pot*0.5
473   #else
774                    pe = pe + pot
775 #endif                
776            
777                drdx = -rxij / r
778                drdy = -ryij / r
779                drdz = -rzij / r
780                
781                fx = dudr * drdx
782                fy = dudr * drdy
783                fz = dudr * drdz
474  
475 +    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
476 +       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
477 +            pot, f)
478 +    endif
479  
480 +    if (Atype_i%is_dp .and. Atype_j%is_dp) then
481 +       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
482 +            pot, u_l, f, t)
483  
484 +       if (do_reaction_field) then
485 +          call accumulate_rf(i, j, r_ij, rt, rrf)
486 +       endif
487  
488 +    endif
489  
490 +    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
491 +       call getstickyforce(r,pot,dudr, Atype_i, Atype_j)
492 +    endif
493  
790                
791 #ifdef IS_MPI
792                fCol(1,j) = fCol(1,j) - fx
793                fCol(2,j) = fCol(2,j) - fy
794                fCol(3,j) = fCol(3,j) - fz
795                
796                fRow(1,j) = fRow(1,j) + fx
797                fRow(2,j) = fRow(2,j) + fy
798                fRow(3,j) = fRow(3,j) + fz
799 #else
800                fTemp(1,j) = fTemp(1,j) - fx
801                fTemp(2,j) = fTemp(2,j) - fy
802                fTemp(3,j) = fTemp(3,j) - fz
803                fTemp(1,i) = fTemp(1,i) + fx
804                fTemp(2,i) = fTemp(2,i) + fy
805                fTemp(3,i) = fTemp(3,i) + fz
494   #endif
807                
808                if (do_stress) then
809                   tauTemp(1) = tauTemp(1) + fx * rxij
810                   tauTemp(2) = tauTemp(2) + fx * ryij
811                   tauTemp(3) = tauTemp(3) + fx * rzij
812                   tauTemp(4) = tauTemp(4) + fy * rxij
813                   tauTemp(5) = tauTemp(5) + fy * ryij
814                   tauTemp(6) = tauTemp(6) + fy * rzij
815                   tauTemp(7) = tauTemp(7) + fz * rxij
816                   tauTemp(8) = tauTemp(8) + fz * ryij
817                   tauTemp(9) = tauTemp(9) + fz * rzij
818                endif
495  
496 <
821 <
496 >      
497    end subroutine do_pair
498  
499  
# Line 920 | Line 595 | contains
595  
596    end subroutine zero_module_variables
597  
598 < #ifdef IS_MPI
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.
602 <  function mpi_cycle_jLoop(i,j) result(do_cycle)
602 >  function checkExcludes(atom1,atom2) result(do_cycle)
603   !--------------- Arguments--------------------------
604   ! Index i
605 <    integer,intent(in) :: i
605 >    integer,intent(in) :: atom1
606   ! Index j
607 <    integer,intent(in) :: j
607 >    integer,intent(in), optional :: atom2
608   ! Result do_cycle
609      logical :: do_cycle
610   !--------------- Local variables--------------------
611      integer :: tag_i
612      integer :: tag_j
613 < !--------------- END DECLARATIONS------------------    
614 <    tag_i = tagRow(i)
613 >    integer :: i
614 > !--------------- END DECLARATIONS------------------  
615 >    do_cycle = .false.
616 >
617 > #ifdef IS_MPI
618 >    tag_i = tagRow(atom1)
619 > #else
620 >    tag_i = tag(atom1)
621 > #endif
622 >
623 > !! Check global excludes first
624 >    if (.not. present(atom2)) then
625 >       do i = 1,nGlobalExcludes
626 >          if (excludeGlobal(i) == tag_i) then
627 >             do_cycle = .true.
628 >             return
629 >          end if
630 >       end do
631 >       return !! return after checking globals
632 >    end if
633 >
634 > !! we return if j not present here.
635      tag_j = tagColumn(j)
636  
637 <    do_cycle = .false.
637 >
638  
639      if (tag_i == tag_j) then
640         do_cycle = .true.
# Line 952 | Line 647 | contains
647      else                
648         if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
649      endif
955  end function mpi_cycle_jLoop
956 #endif
650  
651 +
652 +
653 +    do i = 1, nLocalExcludes
654 +       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
655 +          do_cycle = .true.
656 +          return
657 +       end if
658 +    end do
659 +      
660 +
661 +  end function checkExcludes
662 +
663 +
664   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines