ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/mdtools/md_code/simulation_module.F90
(Generate patch)

Comparing trunk/mdtools/md_code/simulation_module.F90 (file contents):
Revision 241 by mmeineke, Thu Jan 23 16:19:59 2003 UTC vs.
Revision 253 by chuckv, Thu Jan 30 15:20:21 2003 UTC

# Line 11 | Line 11 | module simulation
11  
12    type, public :: simtype
13       PRIVATE
14 <     SEQUENCE
14 > !     SEQUENCE
15   !! Number of particles on this processor
16       integer :: nLRparticles
17   !! Periodic Box    
# Line 38 | Line 38 | module simulation
38    integer, allocatable, dimension(:) :: tag_column
39   #endif
40  
41 <
41 > !! WARNING: use_pbc hardcoded, fixme
42 >  logical :: use_pbc = .true.
43    logical :: setSim = .false.
43  
44  real( kind = dp ), allocatable(:,:),save :: q0
44  
45 + !! array for saving previous positions for neighbor lists.  
46 +  real( kind = dp ), allocatable,dimension(:,:),save :: q0
47 +
48 +
49    public :: check
50    public :: save_nlist
51    public :: wrap
52    public :: getBox
53    public :: getRcut
54 <  public :: setRcut
54 >  public :: getRlist
55 >  public :: getNlocal
56 >  public :: setSimulation
57 > !  public :: setRcut
58  
59    interface wrap
60       module procedure wrap_1d
# Line 76 | Line 82 | contains
82      real(kind = dp ), intent(in), dimension(3) :: box
83      real(kind = dp ), intent(in) :: rlist
84      real(kind = dp ), intent(in) :: rcut
85 <
85 >    integer :: alloc_stat
86      if( setsim ) return  ! simulation is already initialized
87      setSim = .true.
88  
89      thisSim%nLRParticles = nLRParticles
90      thisSim%box          = box
91      thisSim%rlist        = rlist
92 +    thisSIm%rlistsq      = rlist * rlist
93      thisSim%rcut         = rcut
94      thisSim%rcutsq       = rcut * rcut
95 <    thisSim%rcut6        = rcutsq * rcutsq * rcutsq
96 <
95 >    thisSim%rcut6        = thisSim%rcutsq * thisSim%rcutsq * thisSim%rcutsq
96 >    
97 >    if (.not. allocated(q0)) then
98 >       allocate(q0(3,nLRParticles),stat=alloc_stat)
99 >    endif
100    end subroutine setSimulation
101  
102    function getNparticles() result(nparticles)
# Line 103 | Line 113 | contains
113    end subroutine change_box_size
114  
115  
116 <  elemental function getBox_3d() result(thisBox)
116 >  function getBox_3d() result(thisBox)
117      real( kind = dp ), dimension(3) :: thisBox
118      thisBox = thisSim%box
119    end function getBox_3d
# Line 115 | Line 125 | contains
125      thisBox = thisSim%box(dim)
126    end function getBox_dim
127      
128 <  subroutine check(update_nlist)
129 <  
128 >  subroutine check(q,update_nlist)
129 >    real( kind = dp ), dimension(:,:)  :: q
130      integer :: i
131      real( kind = DP ) :: dispmx
132      logical, intent(out) :: update_nlist
133      real( kind = DP ) :: dispmx_tmp
134 <    
134 >    real( kind = dp ) :: skin_thickness
135 >    integer :: natoms
136 >
137 >    natoms = thisSim%nLRparticles
138 >    skin_thickness = thisSim%rlist
139      dispmx = 0.0E0_DP
126    
140      !! calculate the largest displacement of any atom in any direction
141      
142   #ifdef MPI
143      dispmx_tmp = 0.0E0_DP
144 <    do i = 1, nlocal
144 >    do i = 1, thisSim%nLRparticles
145         dispmx_tmp = max( abs ( q(1,i) - q0(1,i) ), dispmx )
146         dispmx_tmp = max( abs ( q(2,i) - q0(2,i) ), dispmx )
147         dispmx_tmp = max( abs ( q(3,i) - q0(3,i) ), dispmx )
# Line 136 | Line 149 | contains
149      call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
150         mpi_max,mpi_comm_world,mpi_err)
151   #else
152 <    do i = 1, natoms
152 >
153 >    do i = 1, thisSim%nLRparticles
154         dispmx = max( abs ( q(1,i) - q0(1,i) ), dispmx )
155         dispmx = max( abs ( q(2,i) - q0(2,i) ), dispmx )
156         dispmx = max( abs ( q(3,i) - q0(3,i) ), dispmx )
# Line 159 | Line 173 | contains
173  
174      if (.not. allocated(q0)) then
175         allocate(q0(3,list_size))
176 <    else if( list_size > size(q0))
176 >    else if( list_size > size(q0)) then
177         deallocate(q0)
178         allocate(q0(3,list_size))
179      endif
# Line 186 | Line 200 | contains
200      return
201    end function wrap_1d
202  
203 <  elemental function wrap_3d(r) result(this_wrap)
203 >  function wrap_3d(r) result(this_wrap)
204      real( kind = dp ), dimension(3), intent(in) :: r
205      real( kind = dp ), dimension(3) :: this_wrap
206  
207      
208      if (use_pbc) then
209         !     this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
210 <       this_wrap(1:3) = r(1:3) - box(1:3)*nint(r(1:3)/box(1:3))
210 >       this_wrap = r - thisSim%box*nint(r/thisSim%box)
211      else
212         this_wrap = r
213      endif
214    end function wrap_3d
215  
216 <
217 <
216 >  
217 >
218    subroutine getRcut(thisrcut,rcut2,rcut6,status)
219      real( kind = dp ), intent(out) :: thisrcut
220      real( kind = dp ), intent(out), optional :: rcut2
221 <    real( kind = dp ), intent(out), optional :: thisrcut6
221 >    real( kind = dp ), intent(out), optional :: rcut6
222      integer, optional :: status
223  
224      if (present(status)) status = 0
# Line 214 | Line 228 | contains
228         return
229      end if
230      
231 <    thisrcut = rcut
232 <    if(present(rcut2)) rcut2 = rcutsq
233 <    if(present(rcut2)) rcut6 = rcut_6
231 >    thisrcut = thisSim%rcut
232 >    if(present(rcut2)) rcut2 = thisSim%rcutsq
233 >    if(present(rcut6)) rcut6 = thisSim%rcut6
234  
235    end subroutine getRcut
236    
237 +  
238 +  
239 +
240 +  subroutine getRlist(thisrlist,rlist2,status)
241 +    real( kind = dp ), intent(out) :: thisrlist
242 +    real( kind = dp ), intent(out), optional :: rlist2
243  
244 +    integer, optional :: status
245  
246 +    if (present(status)) status = 0
247  
248 +    if (.not.setSim ) then
249 +       if (present(status)) status = -1
250 +       return
251 +    end if
252 +    
253 +    thisrlist = thisSim%rlist
254 +    if(present(rlist2)) rlist2 = thisSim%rlistsq
255 +
256 +
257 +  end subroutine getRlist
258 +  
259 +  
260 +
261 + pure function getNlocal() result(nlocal)
262 +    integer :: nlocal
263 +    nlocal = thisSim%nLRparticles
264 +  end function getNlocal
265 +
266 +
267 +
268   end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines