ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/simulation_module.F90
Revision: 482
Committed: Tue Apr 8 22:38:43 2003 UTC (21 years, 3 months ago) by chuckv
File size: 9637 byte(s)
Log Message:
It works (kinda)...

File Contents

# User Rev Content
1 mmeineke 377 !! Fortran interface to C entry plug.
2    
3     module simulation
4     use definitions
5     use neighborLists
6     use force_globals
7     use vector_class
8     use atype_module
9     #ifdef IS_MPI
10     use mpiSimulation
11     #endif
12    
13     implicit none
14     PRIVATE
15    
16     #define __FORTRAN90
17     #include "fSimulation.h"
18    
19     type (simtype), public :: thisSim
20    
21     logical, save :: simulation_setup_complete = .false.
22    
23     integer, public, save :: natoms
24     integer, public, save :: nExcludes_Global = 0
25     integer, public, save :: nExcludes_Local = 0
26     integer, allocatable, dimension(:,:), public :: excludesLocal
27     integer, allocatable, dimension(:), public :: excludesGlobal
28 chuckv 482 integer, allocatable, dimension(:), public :: molMembershipList
29 mmeineke 377
30     real(kind=dp), save :: rcut2 = 0.0_DP
31     real(kind=dp), save :: rcut6 = 0.0_DP
32     real(kind=dp), save :: rlist2 = 0.0_DP
33     real(kind=dp), public, dimension(3), save :: box
34    
35    
36     public :: SimulationSetup
37     public :: getNlocal
38     public :: setBox
39     public :: setBox_3d
40     public :: getBox
41     public :: setRcut
42     public :: getRcut
43     public :: getRlist
44     public :: getRrf
45     public :: getRt
46     public :: getDielect
47     public :: SimUsesPBC
48     public :: SimUsesLJ
49     public :: SimUsesDipoles
50     public :: SimUsesSticky
51     public :: SimUsesRF
52     public :: SimUsesGB
53     public :: SimUsesEAM
54     public :: SimRequiresPrepairCalc
55     public :: SimRequiresPostpairCalc
56     public :: SimUsesDirectionalAtoms
57    
58     interface getBox
59     module procedure getBox_3d
60     module procedure getBox_1d
61     end interface
62    
63     interface setBox
64     module procedure setBox_3d
65     module procedure setBox_1d
66     end interface
67    
68     contains
69    
70     subroutine SimulationSetup(setThisSim, nComponents, c_idents, &
71 chuckv 482 CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, CmolMembership, &
72 mmeineke 377 status)
73    
74     type (simtype) :: setThisSim
75     integer, intent(inout) :: nComponents
76     integer, dimension(nComponents),intent(inout) :: c_idents
77    
78     integer :: CnLocalExcludes
79     integer, dimension(2,CnLocalExcludes), intent(in) :: CexcludesLocal
80     integer :: CnGlobalExcludes
81     integer, dimension(CnGlobalExcludes), intent(in) :: CexcludesGlobal
82 chuckv 482 integer, dimension(nComponents),intent(in) :: CmolMembership
83 mmeineke 377 !! Result status, success = 0, status = -1
84     integer, intent(out) :: status
85     integer :: i, me, thisStat, alloc_stat, myNode
86     #ifdef IS_MPI
87     integer, allocatable, dimension(:) :: c_idents_Row
88     integer, allocatable, dimension(:) :: c_idents_Col
89     integer :: nrow
90     integer :: ncol
91     #endif
92    
93     simulation_setup_complete = .false.
94     status = 0
95    
96     ! copy C struct into fortran type
97     thisSim = setThisSim
98     natoms = nComponents
99     rcut2 = thisSim%rcut * thisSim%rcut
100     rcut6 = rcut2 * rcut2 * rcut2
101     rlist2 = thisSim%rlist * thisSim%rlist
102     box = thisSim%box
103    
104     nExcludes_Global = CnGlobalExcludes
105     nExcludes_Local = CnLocalExcludes
106    
107     call InitializeForceGlobals(natoms, thisStat)
108     if (thisStat /= 0) then
109 chuckv 480 write(default_error,*) "SimSetup: InitializeForceGlobals error"
110 mmeineke 377 status = -1
111     return
112     endif
113    
114     call InitializeSimGlobals(thisStat)
115     if (thisStat /= 0) then
116 chuckv 480 write(default_error,*) "SimSetup: InitializeSimGlobals error"
117 mmeineke 377 status = -1
118     return
119     endif
120    
121     #ifdef IS_MPI
122     ! We can only set up forces if mpiSimulation has been setup.
123     if (.not. isMPISimSet()) then
124     write(default_error,*) "MPI is not set"
125     status = -1
126     return
127     endif
128     nrow = getNrow(plan_row)
129     ncol = getNcol(plan_col)
130     mynode = getMyNode()
131    
132     allocate(c_idents_Row(nrow),stat=alloc_stat)
133     if (alloc_stat /= 0 ) then
134     status = -1
135     return
136     endif
137    
138     allocate(c_idents_Col(ncol),stat=alloc_stat)
139     if (alloc_stat /= 0 ) then
140     status = -1
141     return
142     endif
143    
144     call gather(c_idents, c_idents_Row, plan_row)
145     call gather(c_idents, c_idents_Col, plan_col)
146    
147     do i = 1, nrow
148     me = getFirstMatchingElement(atypes, "c_ident", c_idents_Row(i))
149     atid_Row(i) = me
150     enddo
151    
152     do i = 1, ncol
153     me = getFirstMatchingElement(atypes, "c_ident", c_idents_Col(i))
154     atid_Col(i) = me
155     enddo
156    
157     !! free temporary ident arrays
158     if (allocated(c_idents_Col)) then
159     deallocate(c_idents_Col)
160     end if
161     if (allocated(c_idents_Row)) then
162     deallocate(c_idents_Row)
163     endif
164    
165     #else
166     do i = 1, nComponents
167    
168     me = getFirstMatchingElement(atypes, "c_ident", c_idents(i))
169     atid(i) = me
170    
171     enddo
172     #endif
173    
174    
175 chuckv 388
176 mmeineke 377 do i = 1, nExcludes_Local
177     excludesLocal(1,i) = CexcludesLocal(1,i)
178     excludesLocal(2,i) = CexcludesLocal(2,i)
179     enddo
180    
181     do i = 1, nExcludes_Global
182     excludesGlobal(i) = CexcludesGlobal(i)
183     enddo
184 mmeineke 435
185 chuckv 482 molMemberShipList = CmolMembership
186    
187 mmeineke 377 if (status == 0) simulation_setup_complete = .true.
188    
189     end subroutine SimulationSetup
190    
191     subroutine setBox_3d(new_box_size)
192     real(kind=dp), dimension(3) :: new_box_size
193     integer :: smallest, status, i
194    
195     thisSim%box = new_box_size
196     box = thisSim%box
197    
198     return
199     end subroutine setBox_3d
200    
201     subroutine setBox_1d(dim, new_box_size)
202     integer :: dim, status
203     real(kind=dp) :: new_box_size
204     thisSim%box(dim) = new_box_size
205     box(dim) = thisSim%box(dim)
206     end subroutine setBox_1d
207    
208     subroutine setRcut(new_rcut, status)
209     real(kind = dp) :: new_rcut
210     integer :: myStatus, status
211     thisSim%rcut = new_rcut
212     rcut2 = thisSim%rcut * thisSim%rcut
213     rcut6 = rcut2 * rcut2 * rcut2
214     status = 0
215     return
216     end subroutine setRcut
217    
218     function getBox_3d() result(thisBox)
219     real( kind = dp ), dimension(3) :: thisBox
220     thisBox = thisSim%box
221     end function getBox_3d
222    
223     function getBox_1d(dim) result(thisBox)
224     integer, intent(in) :: dim
225     real( kind = dp ) :: thisBox
226    
227     thisBox = thisSim%box(dim)
228     end function getBox_1d
229    
230     subroutine getRcut(thisrcut,rc2,rc6,status)
231     real( kind = dp ), intent(out) :: thisrcut
232     real( kind = dp ), intent(out), optional :: rc2
233     real( kind = dp ), intent(out), optional :: rc6
234     integer, optional :: status
235    
236     if (present(status)) status = 0
237    
238     if (.not.simulation_setup_complete ) then
239     if (present(status)) status = -1
240     return
241     end if
242    
243     thisrcut = thisSim%rcut
244     if(present(rc2)) rc2 = rcut2
245     if(present(rc6)) rc6 = rcut6
246     end subroutine getRcut
247    
248     subroutine getRlist(thisrlist,rl2,status)
249     real( kind = dp ), intent(out) :: thisrlist
250     real( kind = dp ), intent(out), optional :: rl2
251    
252     integer, optional :: status
253    
254     if (present(status)) status = 0
255    
256     if (.not.simulation_setup_complete ) then
257     if (present(status)) status = -1
258     return
259     end if
260    
261     thisrlist = thisSim%rlist
262     if(present(rl2)) rl2 = rlist2
263     end subroutine getRlist
264    
265     function getRrf() result(rrf)
266     real( kind = dp ) :: rrf
267     rrf = thisSim%rrf
268 gezelter 394 write(*,*) 'getRrf = ', rrf, thisSim%rrf
269 mmeineke 377 end function getRrf
270    
271     function getRt() result(rt)
272     real( kind = dp ) :: rt
273     rt = thisSim%rt
274     end function getRt
275    
276     function getDielect() result(dielect)
277     real( kind = dp ) :: dielect
278     dielect = thisSim%dielect
279     end function getDielect
280    
281     function SimUsesPBC() result(doesit)
282     logical :: doesit
283     doesit = thisSim%SIM_uses_PBC
284     end function SimUsesPBC
285    
286     function SimUsesLJ() result(doesit)
287     logical :: doesit
288     doesit = thisSim%SIM_uses_LJ
289     end function SimUsesLJ
290    
291     function SimUsesSticky() result(doesit)
292     logical :: doesit
293     doesit = thisSim%SIM_uses_sticky
294     end function SimUsesSticky
295    
296     function SimUsesDipoles() result(doesit)
297     logical :: doesit
298     doesit = thisSim%SIM_uses_dipoles
299     end function SimUsesDipoles
300    
301     function SimUsesRF() result(doesit)
302     logical :: doesit
303     doesit = thisSim%SIM_uses_RF
304     end function SimUsesRF
305    
306     function SimUsesGB() result(doesit)
307     logical :: doesit
308     doesit = thisSim%SIM_uses_GB
309     end function SimUsesGB
310    
311     function SimUsesEAM() result(doesit)
312     logical :: doesit
313     doesit = thisSim%SIM_uses_EAM
314     end function SimUsesEAM
315    
316     function SimUsesDirectionalAtoms() result(doesit)
317     logical :: doesit
318     doesit = thisSim%SIM_uses_dipoles .or. thisSim%SIM_uses_sticky .or. &
319     thisSim%SIM_uses_GB .or. thisSim%SIM_uses_RF
320     end function SimUsesDirectionalAtoms
321    
322     function SimRequiresPrepairCalc() result(doesit)
323     logical :: doesit
324     doesit = thisSim%SIM_uses_EAM
325     end function SimRequiresPrepairCalc
326    
327     function SimRequiresPostpairCalc() result(doesit)
328     logical :: doesit
329     doesit = thisSim%SIM_uses_RF
330     end function SimRequiresPostpairCalc
331    
332     subroutine InitializeSimGlobals(thisStat)
333     integer, intent(out) :: thisStat
334     integer :: alloc_stat
335    
336     thisStat = 0
337    
338     call FreeSimGlobals()
339    
340     allocate(excludesLocal(2,nExcludes_Local), stat=alloc_stat)
341     if (alloc_stat /= 0 ) then
342     thisStat = -1
343     return
344     endif
345    
346     allocate(excludesGlobal(nExcludes_Global), stat=alloc_stat)
347     if (alloc_stat /= 0 ) then
348     thisStat = -1
349     return
350     endif
351 chuckv 482
352     allocate(molMembershipList(getNlocal()), stat=alloc_stat)
353     if (alloc_stat /= 0 ) then
354     thisStat = -1
355     return
356     endif
357 mmeineke 377
358     end subroutine InitializeSimGlobals
359    
360     subroutine FreeSimGlobals()
361    
362     !We free in the opposite order in which we allocate in.
363    
364     if (allocated(excludesGlobal)) deallocate(excludesGlobal)
365     if (allocated(excludesLocal)) deallocate(excludesLocal)
366 chuckv 482 if (allocated(molMembershipList)) deallocate(molMembershipList)
367 mmeineke 377 end subroutine FreeSimGlobals
368    
369     pure function getNlocal() result(nlocal)
370     integer :: nlocal
371     nlocal = natoms
372     end function getNlocal
373    
374    
375     end module simulation