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 229 by chuckv, Thu Jan 2 21:45:45 2003 UTC vs.
Revision 230 by chuckv, Thu Jan 9 19:40:38 2003 UTC

# Line 1 | Line 1
1   module simulation
2    use definitions, ONLY :dp
3 <  use force_wrappers, ONLY : alloc_force_wrappers
3 > #ifdef IS_MPI
4 >  use mpiSimulation
5 > #endif
6  
7    implicit none
8    PRIVATE
9  
10  
9  integer :: nLR
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 <  real ( kind = dp ), dimension(3) :: box
30 >  end type simtype
31  
32 +  type (simtype), public :: thisSim
33 + !! Tag for MPI calculations  
34 +  integer, allocatable, dimension(:) :: tag
35  
36 <  real ( kind = dp ), public :: rlist
37 <  real ( kind = dp ), public :: rcut
38 <  real ( kind = dp ), public :: rlistsq
39 <  real ( kind = dp ), public :: rcutsq
36 > #ifdef IS_MPI
37 >  integer, allocatable, dimension(:) :: tag_row
38 >  integer, allocatable, dimension(:) :: tag_column
39 > #endif
40  
20  integer,public, allocatable, dimension(:)   :: point
21  integer,public, allocatable, dimension(:)   :: list
41  
42 +  logical :: setSim = .false.
43 +  
44 +  real( kind = dp ), allocatable(:,:),save :: q0
45  
24
25
26
46    public :: check
47    public :: save_nlist
48    public :: wrap
49    public :: getBox
50 +  public :: getRcut
51 +  public :: setRcut
52  
53    interface wrap
54       module procedure wrap_1d
# Line 40 | Line 61 | module simulation
61    end interface
62  
63  
43 !MPI dependent routines
64  
45 #ifdef IS_MPI
46 ! Universal routines: All types of force calculations will need these arrays
47 ! Arrays specific to a type of force calculation should be declared in that module.
48  real( kind = dp ), allocatable, dimension(:,:) :: qRow
49  real( kind = dp ), allocatable, dimension(:,:) :: qColumn
65  
51  real( kind = dp ), allocatable, dimension(:,:) :: fRow
52  real( kind = dp ), allocatable, dimension(:,:) :: fColumn
66  
54  real( kind = dp ), allocatable, dimension(:,:) :: tRow
55  real( kind = dp ), allocatable, dimension(:,:) :: tColumn
67  
57 #endif
68  
69  
70  
71  
62
63
72   contains
73  
74 < #ifdef MPI
75 < ! Allocated work arrays for MPI
76 <  subroutine allocate_mpi_arrays(nDimensions,numComponents)
77 <    integer, intent(in) :: nDimensions
78 <    integer, intent(in) :: numComponents
74 >  subroutine setSimulation(nLRParticles,box,rlist,rcut)
75 >    integer, intent(in) :: nLRParticles
76 >    real(kind = dp ), intent(in) :: box
77 >    real(kind = dp ), intent(in) :: rlist
78 >    real(kind = dp ), intent(in) :: rcut
79  
80 +    if( setsim ) return  ! simulation is already initialized
81 +    setSim = .true.
82  
83 +    thisSim%nLRParticles = nLRParticles
84 +    thisSim%box          = box
85 +    thisSim%rlist        = rlist
86 +    thisSim%rcut         = rcut
87 +    thisSim%rcutsq       = rcut * rcut
88 +    thisSim%rcut6        = rcutsq * rcutsq * rcutsq
89  
90 +  end subroutine setSimulation
91  
92 +  function getNparticles() result(nparticles)
93 +    integer :: nparticles
94 +    nparticles = thisSim%nLRparticles
95 +  end function getNparticles
96  
76  end subroutine allocate_mpi_arrays
77 #endif
97  
79  subroutine set_simulation(box,rlist,rcut)
80    
81
82
83  end subroutine set_simulation
84
85
86
98    subroutine change_box_size(new_box_size)
99      real(kind=dp), dimension(3) :: new_box_size
100  
101 <    box = new_box_size
101 >    thisSim%box = new_box_size
102  
103    end subroutine change_box_size
104  
105  
106    elemental function getBox_3d() result(thisBox)
107      real( kind = dp ), dimension(3) :: thisBox
108 <    thisBox = box
108 >    thisBox = thisSim%box
109    end function getBox_3d
110  
111    function getBox_dim(dim) result(thisBox)
112      integer, intent(in) :: dim
113      real( kind = dp ) :: thisBox
114  
115 <    thisBox = box(dim)
115 >    thisBox = thisSim%box(dim)
116    end function getBox_dim
117      
118    subroutine check(update_nlist)
# Line 139 | Line 150 | contains
150      
151    end subroutine check
152    
153 <  subroutine save_nlist()
154 <    integer :: i
155 < #ifdef MPI
156 <    do i = 1, nlocal
146 < #else
147 <       do i = 1, natoms
148 < #endif
149 <          q0(1,i) = q(1,i)
150 <          q0(2,i) = q(2,i)
151 <          q0(3,i) = q(3,i)
152 <       end do
153 >  subroutine save_nlist(q)
154 >    real(kind = dp ), dimension(:,:), intent(in)  :: q
155 >    integer :: list_size
156 >    
157  
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  
# Line 163 | Line 178 | contains
178      
179      if (use_pbc) then
180         !     this_wrap = r - box(dim)*dsign(1.0E0_DP,r)*int(abs(r/box(dim)) + 0.5E0_DP)
181 <       this_wrap = r - box(dim)*nint(r/box(dim))
181 >       this_wrap = r - thisSim%box(dim)*nint(r/thisSim%box(dim))
182      else
183         this_wrap = r
184      endif
# Line 184 | Line 199 | contains
199      endif
200    end function wrap_3d
201  
202 +
203 +
204 +  subroutine getRcut(thisrcut,rcut2,rcut6,status)
205 +    real( kind = dp ), intent(out) :: thisrcut
206 +    real( kind = dp ), intent(out), optional :: rcut2
207 +    real( kind = dp ), intent(out), optional :: thisrcut6
208 +    integer, optional :: status
209 +
210 +    if (present(status)) status = 0
211 +
212 +    if (.not.setSim ) then
213 +       if (present(status)) status = -1
214 +       return
215 +    end if
216 +    
217 +    thisrcut = rcut
218 +    if(present(rcut2)) rcut2 = rcutsq
219 +    if(present(rcut2)) rcut6 = rcut_6
220 +
221 +
222 +  end subroutine getRcut
223    
224   end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines