ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90 (file contents):
Revision 306 by chuckv, Mon Mar 10 19:26:45 2003 UTC vs.
Revision 309 by gezelter, Mon Mar 10 23:19:23 2003 UTC

# Line 1 | Line 1
1   module forceGlobals
2  
3 +  use definitions
4 +  use simulation
5 +  use atype_typedefs
6 +  use generic_atypes
7 + #ifdef IS_MPI
8 +  use mpiSimulation
9 + #endif
10  
4
11   !! Number of lj_atypes in lj_atype_list
12    integer, save :: n_atypes = 0
13  
# Line 21 | Line 27 | module forceGlobals
27   !! Column lj_atype pointer list
28    type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
29   #else
30 <  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
30 >  type(identPtrList ), dimension(:), pointer :: identPtrListGlobal => null()
31   #endif
32  
33  
# Line 33 | Line 39 | module forceGlobals
39  
40   !! Potential energy global module variables
41   #ifdef IS_MPI
42 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
43 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
42 >    real( kind = dp ), allocatable, dimension(:,:) :: q_Row
43 >    real( kind = dp ), allocatable, dimension(:,:) :: q_Col
44 >    real( kind = dp ), allocatable, dimension(:,:) :: u_l_Row
45 >    real( kind = dp ), allocatable, dimension(:,:) :: u_l_Col
46 >    real( kind = dp ), allocatable, dimension(:,:) :: A_Row
47 >    real( kind = dp ), allocatable, dimension(:,:) :: A_Col
48  
49 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
50 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
51 <
52 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
53 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
54 <
55 <  real(kind = dp), dimension(9,getNrow(plan_row)) :: ARow = 0.0_dp
56 <  real(kind = dp), dimension(9,getNcol(plan_col)) :: ACol = 0.0_dp  
57 <
48 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
49 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
50 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp1 = 0.0_dp
51 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp1 = 0.0_dp
52 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp2 = 0.0_dp
53 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp2 = 0.0_dp
54 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
55 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
56 <
57 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
58 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
59 <
60 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: rflRow = 0.0_dp
61 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: rflCol = 0.0_dp
62 <  real(kind = dp), dimension(3,getNlocal()) :: rflTemp = 0.0_dp
63 <
64 <  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
65 <  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
66 <
67 <  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
49 >    real( kind = dp ), allocatable, dimension(:) :: pot_Row
50 >    real( kind = dp ), allocatable, dimension(:) :: pot_Col
51 >    real( kind = dp ), allocatable, dimension(:) :: pot_Temp
52 >    real( kind = dp ), allocatable, dimension(:,:) :: f_Row
53 >    real( kind = dp ), allocatable, dimension(:,:) :: f_Col
54 >    real( kind = dp ), allocatable, dimension(:,:) :: f_Temp
55 >    real( kind = dp ), allocatable, dimension(:,:) :: t_Row
56 >    real( kind = dp ), allocatable, dimension(:,:) :: t_Col
57 >    real( kind = dp ), allocatable, dimension(:,:) :: t_Temp
58   #endif
69  real(kind = dp) :: pe = 0.0_dp
70  real(kind = dp), dimension(3,natoms) :: fTemp = 0.0_dp
71  real(kind = dp), dimension(3,natoms) :: tTemp = 0.0_dp
72  real(kind = dp), dimension(3,natoms) :: rflTemp = 0.0_dp
73  real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
59  
60 +  real(kind = dp) :: pot = 0.0_dp
61 +  real(kind = dp), dimension(9) :: tau_Temp = 0.0_dp
62 +  real(kind = dp) :: virial_Temp = 0.0_dp
63 +
64    logical :: do_preForce  = .false.
65    logical :: do_postForce = .false.
66  
# Line 79 | Line 68 | module forceGlobals
68  
69   !! Public methods and data
70    public :: new_atype
82  public :: do_forceLoop
71    public :: init_FF
72  
73    
# Line 88 | Line 76 | contains
76   contains
77  
78   !! Adds a new lj_atype to the list.
79 <  subroutine new_atype(ident,mass,epsilon,sigma, &
79 >  subroutine new_atype(ident, epsilon, sigma, &
80         is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
81 <    real( kind = dp ), intent(in) :: mass
81 >
82      real( kind = dp ), intent(in) :: epsilon
83      real( kind = dp ), intent(in) :: sigma
84      real( kind = dp ), intent(in) :: w0
# Line 122 | Line 110 | contains
110      end if
111  
112   ! assign our new atype information
113 <    the_new_atype%mass        = mass
114 <    the_new_atype%epsilon     = epsilon
115 <    the_new_atype%sigma       = sigma
116 <    the_new_atype%sigma2      = sigma * sigma
117 <    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
118 <         * the_new_atype%sigma2
131 <    the_new_atype%w0       = w0
132 <    the_new_atype%v0       = v0
133 <    the_new_atype%dipoleMoment       = dipoleMoment
113 >
114 >    the_new_atype%lj_epsilon     = epsilon
115 >    the_new_atype%lj_sigma       = sigma
116 >    the_new_atype%sticky_w0       = w0
117 >    the_new_atype%sticky_v0       = v0
118 >    the_new_atype%dipole_moment       = dipoleMoment
119  
120      
121   ! assume that this atype will be successfully added
122      the_new_atype%atype_ident = ident
123 <    the_new_atype%atype_number = n_lj_atypes + 1
123 >    the_new_atype%atype_fortran_index = atype_count + 1
124      
125      if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
126      if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
# Line 147 | Line 132 | contains
132         status = -1
133         return
134      endif
135 <
136 <    n_atypes = n_atypes + 1
137 <
138 <
135 >    
136 >    atype_count = atype_count + 1
137 >    
138 >    
139    end subroutine new_atype
140  
141  
# Line 161 | Line 146 | contains
146   !! ljatype ident.
147      integer, dimension(nComponents),intent(inout) :: ident
148      integer :: nExcludes
149 <    integer, dimension(n),intent(inout) :: excludesLocal
149 >    integer, dimension(nExcludes),intent(inout) :: excludesLocal
150   !!  Result status, success = 0, error = -1
151      integer, intent(out) :: Status
152  
# Line 184 | Line 169 | contains
169  
170   !! if were're not in MPI, we just update ljatypePtrList
171   #ifndef IS_MPI
172 <    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
172 >    call create_IdentPtrList(ident,ListHead,identPtrListGlobal,thisStat)
173      if ( thisStat /= 0 ) then
174         status = -1
175         return
# Line 260 | Line 245 | contains
245      endif
246  
247      isFFinit = .true.
248 <
249 <
248 >    
249 >    
250    end subroutine init_FF
251 +
252  
253  
268
269
254    subroutine initForce_Modules(thisStat)
255      integer, intent(out) :: thisStat
256      integer :: my_status
# Line 281 | Line 265 | contains
265    end subroutine initForce_Modules
266  
267  
284
285
286
287
288
268   end module forceGlobals

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines