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

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/simulation_module.F90 (file contents):
Revision 270 by mmeineke, Fri Feb 14 17:08:46 2003 UTC vs.
Revision 312 by gezelter, Tue Mar 11 17:46:18 2003 UTC

# Line 1 | Line 1
1 + !! Fortran interface to C entry plug.
2 +
3   module simulation
4    use definitions, ONLY :dp
5   #ifdef IS_MPI
# Line 7 | Line 9 | module simulation
9    implicit none
10    PRIVATE
11  
12 + #define __FORTRAN90
13 + #include "fSimulation.h"
14  
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
15    type (simtype), public :: thisSim
33 !! Tag for MPI calculations  
34  integer, allocatable, dimension(:) :: tag
16  
36 #ifdef IS_MPI
37  integer, allocatable, dimension(:) :: tag_row
38  integer, allocatable, dimension(:) :: tag_column
39 #endif
40
41 !! WARNING: use_pbc hardcoded, fixme
42  logical :: use_pbc = .true.
17    logical :: setSim = .false.
18  
19 < !! array for saving previous positions for neighbor lists.  
46 <  real( kind = dp ), allocatable,dimension(:,:),save :: q0
19 >  integer,public :: natoms
20  
48
49  public :: check
50  public :: save_nlist
51  public :: wrap
21    public :: getBox
22    public :: getRcut
23    public :: getRlist
24 +  public :: getRrf
25 +  public :: getRt
26    public :: getNlocal
27    public :: setSimulation
28 < !  public :: setRcut
28 >  public :: isEnsemble
29 >  public :: isPBC
30 >  public :: getStringLen
31 >  public :: returnMixingRules
32 >  public :: doStress
33  
34 <  interface wrap
60 <     module procedure wrap_1d
61 <     module procedure wrap_3d
62 <  end interface
63 <
34 > !  public :: setRcut
35    interface getBox
36       module procedure getBox_3d
37       module procedure getBox_dim
38    end interface
39  
69
70
71
72
73
74
75
76
77
40   contains
41  
42 <  subroutine setSimulation(nLRParticles,box,rlist,rcut)
43 <    integer, intent(in) :: nLRParticles
44 <    real(kind = dp ), intent(in), dimension(3) :: box
83 <    real(kind = dp ), intent(in) :: rlist
84 <    real(kind = dp ), intent(in) :: rcut
42 >  subroutine setSimulation(setThisSim,error)
43 >    type (simtype) :: setThisSim
44 >    integer :: error
45      integer :: alloc_stat
86    if( setsim ) return  ! simulation is already initialized
87    setSim = .true.
46  
47 <    thisSim%nLRParticles = nLRParticles
48 <    thisSim%box          = box
49 <    thisSim%rlist        = rlist
50 <    thisSIm%rlistsq      = rlist * rlist
93 <    thisSim%rcut         = rcut
94 <    thisSim%rcutsq       = rcut * rcut
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
47 >    error = 0
48 >    setSim = .true.
49 >    ! copy C struct into fortran type
50 >    thisSim = setThisSim
51    end subroutine setSimulation
52  
53    function getNparticles() result(nparticles)
# Line 104 | Line 55 | contains
55      nparticles = thisSim%nLRparticles
56    end function getNparticles
57  
107
58    subroutine change_box_size(new_box_size)
59      real(kind=dp), dimension(3) :: new_box_size
110
60      thisSim%box = new_box_size
112
61    end subroutine change_box_size
62  
115
63    function getBox_3d() result(thisBox)
64      real( kind = dp ), dimension(3) :: thisBox
65      thisBox = thisSim%box
# Line 121 | Line 68 | contains
68    function getBox_dim(dim) result(thisBox)
69      integer, intent(in) :: dim
70      real( kind = dp ) :: thisBox
71 <
71 >    
72      thisBox = thisSim%box(dim)
73    end function getBox_dim
74 <    
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 <    real( kind = dp ) :: skin_thickness
135 <    integer :: natoms
136 <
137 <    natoms = thisSim%nLRparticles
138 <    skin_thickness = thisSim%rlist - thisSim%rcut
139 <    dispmx = 0.0E0_DP
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, 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 )
148 <    end do
149 <    call mpi_allreduce(dispmx_tmp,dispmx,1,mpi_double_precision, &
150 <       mpi_max,mpi_comm_world,mpi_err)
151 < #else
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 )
157 <    end do
158 < #endif
159 <  
160 <    !! a conservative test of list skin crossings
161 <    dispmx = 2.0E0_DP * sqrt (3.0E0_DP * dispmx * dispmx)
162 <    
163 <    update_nlist = (dispmx.gt.(skin_thickness))
164 <    
165 <  end subroutine check
166 <  
167 <  subroutine save_nlist(q)
168 <    real(kind = dp ), dimension(:,:), intent(in)  :: q
169 <    integer :: list_size
170 <    
171 <
172 <    list_size = size(q)
173 <
174 <    if (.not. allocated(q0)) then
175 <       allocate(q0(3,list_size))
176 <    else if( list_size > size(q0)) then
177 <       deallocate(q0)
178 <       allocate(q0(3,list_size))
179 <    endif
180 <
181 <    q0 = q
182 <
183 <  end subroutine save_nlist
184 <  
185 <
186 <  function wrap_1d(r,dim) result(this_wrap)
187 <    
188 <    
189 <    real( kind = DP ) :: r
190 <    real( kind = DP ) :: this_wrap
191 <    integer           :: dim
192 <    
193 <    if (use_pbc) then
194 <       !     this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
195 <       this_wrap = r - thisSim%box(dim)*nint(r/thisSim%box(dim))
196 <    else
197 <       this_wrap = r
198 <    endif
199 <    
200 <    return
201 <  end function wrap_1d
202 <
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 = r - thisSim%box*nint(r/thisSim%box)
211 <    else
212 <       this_wrap = r
213 <    endif
214 <  end function wrap_3d
215 <
216 <  
217 <
74 >    
75    subroutine getRcut(thisrcut,rcut2,rcut6,status)
76      real( kind = dp ), intent(out) :: thisrcut
77      real( kind = dp ), intent(out), optional :: rcut2
# Line 231 | Line 88 | contains
88      thisrcut = thisSim%rcut
89      if(present(rcut2)) rcut2 = thisSim%rcutsq
90      if(present(rcut6)) rcut6 = thisSim%rcut6
234
91    end subroutine getRcut
92    
237  
238  
239
93    subroutine getRlist(thisrlist,rlist2,status)
94      real( kind = dp ), intent(out) :: thisrlist
95      real( kind = dp ), intent(out), optional :: rlist2
# Line 252 | Line 105 | contains
105      
106      thisrlist = thisSim%rlist
107      if(present(rlist2)) rlist2 = thisSim%rlistsq
255
256
108    end subroutine getRlist
258  
259  
109  
110 < pure function getNlocal() result(nlocal)
110 >  function getRrf() result(rrf)
111 >    real( kind = dp ) :: rrf
112 >    rrf = thisSim%rrf
113 >  end function getRrf
114 >  
115 >  function getRt() result(rt)
116 >    real( kind = dp ) :: rt
117 >    rt = thisSim%rt
118 >  end function getRt
119 >  
120 >  pure function getNlocal() result(nlocal)
121      integer :: nlocal
122      nlocal = thisSim%nLRparticles
123    end function getNlocal
124 <
125 <
126 <
124 >  
125 >  function doStress() result(do_stress)
126 >    logical :: do_stress
127 >    do_stress = thisSim%do_stress
128 >  end function doStress
129 >  
130 >  function isEnsemble(this_ensemble) result(is_this_ensemble)
131 >    character(len = *) :: this_ensemble
132 >    logical :: is_this_ensemble
133 >    is_this_ensemble = .false.
134 >    if (this_ensemble == thisSim%ensemble) is_this_ensemble = .true.
135 >  end function isEnsemble
136 >  
137 >  function returnEnsemble() result(thisEnsemble)
138 >    character (len = len(thisSim%ensemble)) :: thisEnsemble
139 >    thisEnsemble = thisSim%ensemble
140 >  end function returnEnsemble
141 >  
142 >  function returnMixingRules() result(thisMixingRule)
143 >    character (len = len(thisSim%ensemble)) :: thisMixingRule
144 >    thisMixingRule = thisSim%MixingRule
145 >  end function returnMixingRules
146 >  
147 >  function isPBC() result(PBCset)
148 >    logical :: PBCset
149 >    PBCset = .false.
150 >    if (thisSim%use_pbc) PBCset = .true.
151 >  end function isPBC
152 >  
153 >  pure function getStringLen() result (thislen)
154 >    integer :: thislen    
155 >    thislen = string_len
156 >  end function getStringLen
157 >  
158   end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines