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 240 by chuckv, Wed Jan 22 21:45:20 2003 UTC vs.
Revision 281 by chuckv, Mon Feb 24 21:25:15 2003 UTC

# Line 7 | Line 7 | module simulation
7    implicit none
8    PRIVATE
9  
10 + #define __FORTRAN90
11 + #include "../headers/fsimulation.h"
12  
11
12  type, public :: simtype
13     PRIVATE
14     SEQUENCE
15 !! Number of particles on this processor
16     integer :: nLRparticles
17 !! Periodic Box    
18     real ( kind = dp ), dimension(3) :: box
19 !! List Cutoff    
20     real ( kind = dp ) :: rlist = 0.0_dp
21 !! Radial cutoff
22     real ( kind = dp ) :: rcut  = 0.0_dp
23 !! List cutoff squared
24     real ( kind = dp ) :: rlistsq = 0.0_dp
25 !! Radial Cutoff squared
26     real ( kind = dp ) :: rcutsq  = 0.0_dp
27 !! Radial Cutoff^6
28     real ( kind = dp ) :: rcut6  = 0.0_dp
29
30  end type simtype
31
13    type (simtype), public :: thisSim
14   !! Tag for MPI calculations  
15    integer, allocatable, dimension(:) :: tag
# Line 38 | Line 19 | module simulation
19    integer, allocatable, dimension(:) :: tag_column
20   #endif
21  
22 + !! WARNING: use_pbc hardcoded, fixme
23 +   logical :: setSim = .false.
24  
25 <  logical :: setSim = .false.
26 <  
44 <  real( kind = dp ), allocatable(:,:),save :: q0
25 > !! array for saving previous positions for neighbor lists.  
26 >  real( kind = dp ), allocatable,dimension(:,:),save :: q0
27  
28 +
29    public :: check
30    public :: save_nlist
31    public :: wrap
32    public :: getBox
33    public :: getRcut
34 <  public :: setRcut
34 >  public :: getRlist
35 >  public :: getNlocal
36 >  public :: setSimulation
37 >  public :: isEnsemble
38 >  public :: isPBC
39 >  public :: getStringLen
40 >  public :: returnMixingRules
41  
42 + !  public :: setRcut
43 +
44    interface wrap
45       module procedure wrap_1d
46       module procedure wrap_3d
# Line 71 | Line 62 | contains
62  
63   contains
64  
65 <  subroutine setSimulation(nLRParticles,box,rlist,rcut)
65 >  subroutine setSimulation(nLRParticles,box,rlist,rcut,ensemble,mixingRule,use_pbc)
66      integer, intent(in) :: nLRParticles
67 <    real(kind = dp ), intent(in) :: box
67 >    real(kind = dp ), intent(in), dimension(3) :: box
68      real(kind = dp ), intent(in) :: rlist
69      real(kind = dp ), intent(in) :: rcut
70 <
70 >    character( len = stringLen), intent(in)  :: ensemble
71 >    character( len = stringLen), intent(in)  :: mixingRule
72 >    logical, intent(in) :: use_pbc
73 >    integer :: alloc_stat
74      if( setsim ) return  ! simulation is already initialized
75      setSim = .true.
76  
77      thisSim%nLRParticles = nLRParticles
78      thisSim%box          = box
79      thisSim%rlist        = rlist
80 +    thisSIm%rlistsq      = rlist * rlist
81      thisSim%rcut         = rcut
82      thisSim%rcutsq       = rcut * rcut
83 <    thisSim%rcut6        = rcutsq * rcutsq * rcutsq
83 >    thisSim%rcut6        = thisSim%rcutsq * thisSim%rcutsq * thisSim%rcutsq
84 >    
85 >    thisSim%ensemble = ensemble
86 >    thisSim%mixingRule = mixingRule
87 >    thisSim%use_pbc = use_pbc
88  
89 +    if (.not. allocated(q0)) then
90 +       allocate(q0(3,nLRParticles),stat=alloc_stat)
91 +    endif
92    end subroutine setSimulation
93  
94    function getNparticles() result(nparticles)
# Line 103 | Line 105 | contains
105    end subroutine change_box_size
106  
107  
108 <  elemental function getBox_3d() result(thisBox)
108 >  function getBox_3d() result(thisBox)
109      real( kind = dp ), dimension(3) :: thisBox
110      thisBox = thisSim%box
111    end function getBox_3d
# Line 115 | Line 117 | contains
117      thisBox = thisSim%box(dim)
118    end function getBox_dim
119      
120 <  subroutine check(update_nlist)
121 <  
120 >  subroutine check(q,update_nlist)
121 >    real( kind = dp ), dimension(:,:)  :: q
122      integer :: i
123      real( kind = DP ) :: dispmx
124      logical, intent(out) :: update_nlist
125      real( kind = DP ) :: dispmx_tmp
126 <    
126 >    real( kind = dp ) :: skin_thickness
127 >    integer :: natoms
128 >
129 >    natoms = thisSim%nLRparticles
130 >    skin_thickness = thisSim%rlist - thisSim%rcut
131      dispmx = 0.0E0_DP
126    
132      !! calculate the largest displacement of any atom in any direction
133      
134   #ifdef MPI
135      dispmx_tmp = 0.0E0_DP
136 <    do i = 1, nlocal
136 >    do i = 1, thisSim%nLRparticles
137         dispmx_tmp = max( abs ( q(1,i) - q0(1,i) ), dispmx )
138         dispmx_tmp = max( abs ( q(2,i) - q0(2,i) ), dispmx )
139         dispmx_tmp = max( abs ( q(3,i) - q0(3,i) ), dispmx )
# Line 136 | Line 141 | contains
141      call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
142         mpi_max,mpi_comm_world,mpi_err)
143   #else
144 <    do i = 1, natoms
144 >
145 >    do i = 1, thisSim%nLRparticles
146         dispmx = max( abs ( q(1,i) - q0(1,i) ), dispmx )
147         dispmx = max( abs ( q(2,i) - q0(2,i) ), dispmx )
148         dispmx = max( abs ( q(3,i) - q0(3,i) ), dispmx )
# Line 159 | Line 165 | contains
165  
166      if (.not. allocated(q0)) then
167         allocate(q0(3,list_size))
168 <    else if( list_size > size(q0))
168 >    else if( list_size > size(q0)) then
169         deallocate(q0)
170         allocate(q0(3,list_size))
171      endif
# Line 186 | Line 192 | contains
192      return
193    end function wrap_1d
194  
195 <  elemental function wrap_3d(r) result(this_wrap)
195 >  function wrap_3d(r) result(this_wrap)
196      real( kind = dp ), dimension(3), intent(in) :: r
197      real( kind = dp ), dimension(3) :: this_wrap
198  
199      
200 <    if (use_pbc) then
200 >    if (this_sim%use_pbc) then
201         !     this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
202 <       this_wrap(1:3) = r(1:3) - box(1:3)*nint(r(1:3)/box(1:3))
202 >       this_wrap = r - thisSim%box*nint(r/thisSim%box)
203      else
204         this_wrap = r
205      endif
206    end function wrap_3d
207  
208 <
209 <
208 >  
209 >
210    subroutine getRcut(thisrcut,rcut2,rcut6,status)
211      real( kind = dp ), intent(out) :: thisrcut
212      real( kind = dp ), intent(out), optional :: rcut2
213 <    real( kind = dp ), intent(out), optional :: thisrcut6
213 >    real( kind = dp ), intent(out), optional :: rcut6
214      integer, optional :: status
215  
216      if (present(status)) status = 0
# Line 214 | Line 220 | contains
220         return
221      end if
222      
223 <    thisrcut = rcut
224 <    if(present(rcut2)) rcut2 = rcutsq
225 <    if(present(rcut2)) rcut6 = rcut_6
223 >    thisrcut = thisSim%rcut
224 >    if(present(rcut2)) rcut2 = thisSim%rcutsq
225 >    if(present(rcut6)) rcut6 = thisSim%rcut6
226  
227    end subroutine getRcut
228    
229 +  
230 +  
231 +
232 +  subroutine getRlist(thisrlist,rlist2,status)
233 +    real( kind = dp ), intent(out) :: thisrlist
234 +    real( kind = dp ), intent(out), optional :: rlist2
235  
236 +    integer, optional :: status
237  
238 +    if (present(status)) status = 0
239  
240 +    if (.not.setSim ) then
241 +       if (present(status)) status = -1
242 +       return
243 +    end if
244 +    
245 +    thisrlist = thisSim%rlist
246 +    if(present(rlist2)) rlist2 = thisSim%rlistsq
247 +
248 +
249 +  end subroutine getRlist
250 +  
251 +  
252 +
253 + pure function getNlocal() result(nlocal)
254 +    integer :: nlocal
255 +    nlocal = thisSim%nLRparticles
256 +  end function getNlocal
257 +
258 +
259 +  function isEnsemble(this_ensemble) result(is_this_ensemble)
260 +    character(len = *) :: this_ensemble
261 +    logical :: is_this_enemble
262 +    is_this_ensemble = .false.
263 +    if (this_ensemble == thisSim%ensemble) is_this_ensemble = .true.
264 +  end function isEnsemble
265 +
266 +  function returnEnsemble() result(thisEnsemble)
267 +    character (len = len(thisSim%ensemble)) :: thisEnsemble
268 +    thisEnsemble = thisSim%ensemble
269 +  end function returnEnsemble
270 +
271 +  function returnMixingRules() result(thisMixingRule)
272 +    character (len = len(thisSim%ensemble)) :: thisMixingRule
273 +    thisMixingRule = thisSim%MixingRule
274 +  end function returnMixingRules
275 +
276 +  function isPBC() result(PBCset)
277 +    logical :: PBCset
278 +    PBCset = .false.
279 +    if (thisSim%use_pbc) PBCset = .true.
280 +  end function isPBC
281 +
282 +  pure function getStringLen() result (thislen)
283 +    integer :: thislen    
284 +    thislen = string_len
285 +  end function setStringLen
286 +
287   end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines