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 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 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 <  public :: check
47 <  public :: save_nlist
28 >
29    public :: wrap
30    public :: getBox
31    public :: getRcut
32 <  public :: setRcut
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
43       module procedure wrap_1d
44       module procedure wrap_3d
# Line 71 | 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) :: box
65 >    real(kind = dp ), intent(in), dimension(3) :: box
66      real(kind = dp ), intent(in) :: rlist
67      real(kind = dp ), intent(in) :: rcut
68 <
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.
74  
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        = rcutsq * rcutsq * rcutsq
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
90    end subroutine setSimulation
91  
92    function getNparticles() result(nparticles)
# Line 103 | Line 103 | contains
103    end subroutine change_box_size
104  
105  
106 <  elemental function getBox_3d() result(thisBox)
106 >  function getBox_3d() result(thisBox)
107      real( kind = dp ), dimension(3) :: thisBox
108      thisBox = thisSim%box
109    end function getBox_3d
# Line 114 | Line 114 | contains
114  
115      thisBox = thisSim%box(dim)
116    end function getBox_dim
117    
118  subroutine check(update_nlist)
117    
120    integer :: i
121    real( kind = DP ) :: dispmx
122    logical, intent(out) :: update_nlist
123    real( kind = DP ) :: dispmx_tmp
124    
125    dispmx = 0.0E0_DP
126    
127    !! calculate the largest displacement of any atom in any direction
128    
129 #ifdef MPI
130    dispmx_tmp = 0.0E0_DP
131    do i = 1, nlocal
132       dispmx_tmp = max( abs ( q(1,i) - q0(1,i) ), dispmx )
133       dispmx_tmp = max( abs ( q(2,i) - q0(2,i) ), dispmx )
134       dispmx_tmp = max( abs ( q(3,i) - q0(3,i) ), dispmx )
135    end do
136    call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
137       mpi_max,mpi_comm_world,mpi_err)
138 #else
139    do i = 1, natoms
140       dispmx = max( abs ( q(1,i) - q0(1,i) ), dispmx )
141       dispmx = max( abs ( q(2,i) - q0(2,i) ), dispmx )
142       dispmx = max( abs ( q(3,i) - q0(3,i) ), dispmx )
143    end do
144 #endif
145  
146    !! a conservative test of list skin crossings
147    dispmx = 2.0E0_DP * sqrt (3.0E0_DP * dispmx * dispmx)
148    
149    update_nlist = (dispmx.gt.(skin_thickness))
150    
151  end subroutine check
152  
153  subroutine save_nlist(q)
154    real(kind = dp ), dimension(:,:), intent(in)  :: q
155    integer :: list_size
156    
118  
158    list_size = size(q)
159
160    if (.not. allocated(q0)) then
161       allocate(q0(3,list_size))
162    else if( list_size > size(q0))
163       deallocate(q0)
164       allocate(q0(3,list_size))
165    endif
166
167    q0 = q
168
169  end subroutine save_nlist
170  
171
119    function wrap_1d(r,dim) result(this_wrap)
120      
121      
# Line 186 | Line 133 | contains
133      return
134    end function wrap_1d
135  
136 <  elemental function wrap_3d(r) result(this_wrap)
136 >  function wrap_3d(r) result(this_wrap)
137      real( kind = dp ), dimension(3), intent(in) :: r
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(1:3) = r(1:3) - box(1:3)*nint(r(1:3)/box(1:3))
143 >       this_wrap = r - thisSim%box*nint(r/thisSim%box)
144      else
145         this_wrap = r
146      endif
147    end function wrap_3d
148  
149 <
150 <
149 >  
150 >
151    subroutine getRcut(thisrcut,rcut2,rcut6,status)
152      real( kind = dp ), intent(out) :: thisrcut
153      real( kind = dp ), intent(out), optional :: rcut2
154 <    real( kind = dp ), intent(out), optional :: thisrcut6
154 >    real( kind = dp ), intent(out), optional :: rcut6
155      integer, optional :: status
156  
157      if (present(status)) status = 0
# Line 214 | Line 161 | contains
161         return
162      end if
163      
164 <    thisrcut = rcut
165 <    if(present(rcut2)) rcut2 = rcutsq
166 <    if(present(rcut2)) rcut6 = rcut_6
164 >    thisrcut = thisSim%rcut
165 >    if(present(rcut2)) rcut2 = thisSim%rcutsq
166 >    if(present(rcut6)) rcut6 = thisSim%rcut6
167  
168    end subroutine getRcut
169    
170 +  
171 +  
172 +
173 +  subroutine getRlist(thisrlist,rlist2,status)
174 +    real( kind = dp ), intent(out) :: thisrlist
175 +    real( kind = dp ), intent(out), optional :: rlist2
176  
177 +    integer, optional :: status
178  
179 +    if (present(status)) status = 0
180  
181 +    if (.not.setSim ) then
182 +       if (present(status)) status = -1
183 +       return
184 +    end if
185 +    
186 +    thisrlist = thisSim%rlist
187 +    if(present(rlist2)) rlist2 = thisSim%rlistsq
188 +
189 +
190 +  end subroutine getRlist
191 +  
192 +  
193 +
194 + pure function getNlocal() result(nlocal)
195 +    integer :: nlocal
196 +    nlocal = thisSim%nLRparticles
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