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 252 by chuckv, Tue Jan 28 22:16:55 2003 UTC vs.
Revision 284 by chuckv, Tue Feb 25 21:30:09 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 39 | Line 20 | module simulation
20   #endif
21  
22   !! WARNING: use_pbc hardcoded, fixme
23 <  logical :: use_pbc = .true.
43 <  logical :: setSim = .false.
23 >   logical :: setSim = .false.
24  
25   !! array for saving previous positions for neighbor lists.  
26    real( kind = dp ), allocatable,dimension(:,:),save :: q0
27  
28  
49  public :: check
50  public :: save_nlist
29    public :: wrap
30    public :: getBox
31    public :: getRcut
32    public :: getRlist
33    public :: getNlocal
34    public :: setSimulation
35 +  public :: isEnsemble
36 +  public :: isPBC
37 +  public :: getStringLen
38 +  public :: returnMixingRules
39 +
40   !  public :: setRcut
41  
42    interface wrap
# Line 77 | Line 60 | contains
60  
61   contains
62  
63 <  subroutine setSimulation(nLRParticles,box,rlist,rcut)
63 >  subroutine setSimulation(nLRParticles,box,rlist,rcut,ensemble,mixingRule,use_pbc)
64      integer, intent(in) :: nLRParticles
65      real(kind = dp ), intent(in), dimension(3) :: box
66      real(kind = dp ), intent(in) :: rlist
67      real(kind = dp ), intent(in) :: rcut
68 +    character( len = stringLen), intent(in)  :: ensemble
69 +    character( len = stringLen), intent(in)  :: mixingRule
70 +    logical, intent(in) :: use_pbc
71      integer :: alloc_stat
72      if( setsim ) return  ! simulation is already initialized
73      setSim = .true.
# Line 89 | Line 75 | contains
75      thisSim%nLRParticles = nLRParticles
76      thisSim%box          = box
77      thisSim%rlist        = rlist
78 +    thisSIm%rlistsq      = rlist * rlist
79      thisSim%rcut         = rcut
80      thisSim%rcutsq       = rcut * rcut
81      thisSim%rcut6        = thisSim%rcutsq * thisSim%rcutsq * thisSim%rcutsq
82      
83 +    thisSim%ensemble = ensemble
84 +    thisSim%mixingRule = mixingRule
85 +    thisSim%use_pbc = use_pbc
86 +
87      if (.not. allocated(q0)) then
88         allocate(q0(3,nLRParticles),stat=alloc_stat)
89      endif
# Line 123 | Line 114 | contains
114  
115      thisBox = thisSim%box(dim)
116    end function getBox_dim
126    
127  subroutine check(q,update_nlist)
128    real( kind = dp ), dimension(:,:)  :: q
129    integer :: i
130    real( kind = DP ) :: dispmx
131    logical, intent(out) :: update_nlist
132    real( kind = DP ) :: dispmx_tmp
133    real( kind = dp ) :: skin_thickness
134    integer :: natoms
135
136    natoms = thisSim%nLRparticles
137    skin_thickness = thisSim%rlist
138    dispmx = 0.0E0_DP
139    !! calculate the largest displacement of any atom in any direction
140    
141 #ifdef MPI
142    dispmx_tmp = 0.0E0_DP
143    do i = 1, thisSim%nLRparticles
144       dispmx_tmp = max( abs ( q(1,i) - q0(1,i) ), dispmx )
145       dispmx_tmp = max( abs ( q(2,i) - q0(2,i) ), dispmx )
146       dispmx_tmp = max( abs ( q(3,i) - q0(3,i) ), dispmx )
147    end do
148    call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
149       mpi_max,mpi_comm_world,mpi_err)
150 #else
151
152    do i = 1, thisSim%nLRparticles
153       dispmx = max( abs ( q(1,i) - q0(1,i) ), dispmx )
154       dispmx = max( abs ( q(2,i) - q0(2,i) ), dispmx )
155       dispmx = max( abs ( q(3,i) - q0(3,i) ), dispmx )
156    end do
157 #endif
117    
159    !! a conservative test of list skin crossings
160    dispmx = 2.0E0_DP * sqrt (3.0E0_DP * dispmx * dispmx)
161    
162    update_nlist = (dispmx.gt.(skin_thickness))
163    
164  end subroutine check
165  
166  subroutine save_nlist(q)
167    real(kind = dp ), dimension(:,:), intent(in)  :: q
168    integer :: list_size
169    
118  
171    list_size = size(q)
172
173    if (.not. allocated(q0)) then
174       allocate(q0(3,list_size))
175    else if( list_size > size(q0)) then
176       deallocate(q0)
177       allocate(q0(3,list_size))
178    endif
179
180    q0 = q
181
182  end subroutine save_nlist
183  
184
119    function wrap_1d(r,dim) result(this_wrap)
120      
121      
# Line 204 | Line 138 | contains
138      real( kind = dp ), dimension(3) :: this_wrap
139  
140      
141 <    if (use_pbc) then
141 >    if (this_sim%use_pbc) then
142         !     this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
143         this_wrap = r - thisSim%box*nint(r/thisSim%box)
144      else
# Line 252 | Line 186 | contains
186      thisrlist = thisSim%rlist
187      if(present(rlist2)) rlist2 = thisSim%rlistsq
188  
189 +
190    end subroutine getRlist
191    
192    
# Line 262 | Line 197 | contains
197    end function getNlocal
198  
199  
200 +  function isEnsemble(this_ensemble) result(is_this_ensemble)
201 +    character(len = *) :: this_ensemble
202 +    logical :: is_this_enemble
203 +    is_this_ensemble = .false.
204 +    if (this_ensemble == thisSim%ensemble) is_this_ensemble = .true.
205 +  end function isEnsemble
206  
207 +  function returnEnsemble() result(thisEnsemble)
208 +    character (len = len(thisSim%ensemble)) :: thisEnsemble
209 +    thisEnsemble = thisSim%ensemble
210 +  end function returnEnsemble
211 +
212 +  function returnMixingRules() result(thisMixingRule)
213 +    character (len = len(thisSim%ensemble)) :: thisMixingRule
214 +    thisMixingRule = thisSim%MixingRule
215 +  end function returnMixingRules
216 +
217 +  function isPBC() result(PBCset)
218 +    logical :: PBCset
219 +    PBCset = .false.
220 +    if (thisSim%use_pbc) PBCset = .true.
221 +  end function isPBC
222 +
223 +  pure function getStringLen() result (thislen)
224 +    integer :: thislen    
225 +    thislen = string_len
226 +  end function setStringLen
227 +
228   end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines