ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/simulation.F90
Revision: 3135
Committed: Sat May 26 17:53:04 2007 UTC (17 years, 3 months ago) by chuckv
File size: 23661 byte(s)
Log Message:
Removed debug message from simParallel.

File Contents

# Content
1 !!
2 !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3 !!
4 !! The University of Notre Dame grants you ("Licensee") a
5 !! non-exclusive, royalty free, license to use, modify and
6 !! redistribute this software in source and binary code form, provided
7 !! that the following conditions are met:
8 !!
9 !! 1. Acknowledgement of the program authors must be made in any
10 !! publication of scientific results based in part on use of the
11 !! program. An acceptable form of acknowledgement is citation of
12 !! the article in which the program was described (Matthew
13 !! A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14 !! J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15 !! Parallel Simulation Engine for Molecular Dynamics,"
16 !! J. Comput. Chem. 26, pp. 252-271 (2005))
17 !!
18 !! 2. Redistributions of source code must retain the above copyright
19 !! notice, this list of conditions and the following disclaimer.
20 !!
21 !! 3. Redistributions in binary form must reproduce the above copyright
22 !! notice, this list of conditions and the following disclaimer in the
23 !! documentation and/or other materials provided with the
24 !! distribution.
25 !!
26 !! This software is provided "AS IS," without a warranty of any
27 !! kind. All express or implied conditions, representations and
28 !! warranties, including any implied warranty of merchantability,
29 !! fitness for a particular purpose or non-infringement, are hereby
30 !! excluded. The University of Notre Dame and its licensors shall not
31 !! be liable for any damages suffered by licensee as a result of
32 !! using, modifying or distributing the software or its
33 !! derivatives. In no event will the University of Notre Dame or its
34 !! licensors be liable for any lost revenue, profit or data, or for
35 !! direct, indirect, special, consequential, incidental or punitive
36 !! damages, however caused and regardless of the theory of liability,
37 !! arising out of the use of or inability to use software, even if the
38 !! University of Notre Dame has been advised of the possibility of
39 !! such damages.
40 !!
41
42 !! Fortran interface to C entry plug.
43
44 module simulation
45 use definitions
46 use status
47 use linearAlgebra
48 use neighborLists
49 use force_globals
50 use vector_class
51 use atype_module
52 use switcheroo
53 #ifdef IS_MPI
54 use mpiSimulation
55 #endif
56
57 implicit none
58 PRIVATE
59
60 #define __FORTRAN90
61 #include "brains/fSimulation.h"
62 #include "UseTheForce/fSwitchingFunction.h"
63 #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
64
65 type (simtype), public, save :: thisSim
66
67 logical, save :: simulation_setup_complete = .false.
68
69 integer, public, save :: nLocal, nGlobal
70 integer, public, save :: nGroups, nGroupGlobal
71 integer, public, save :: nExcludes_Global = 0
72 integer, public, save :: nExcludes_Local = 0
73 integer, allocatable, dimension(:,:), public :: excludesLocal
74 integer, allocatable, dimension(:), public :: excludesGlobal
75 integer, allocatable, dimension(:), public :: molMembershipList
76 integer, allocatable, dimension(:), public :: groupListRow
77 integer, allocatable, dimension(:), public :: groupStartRow
78 integer, allocatable, dimension(:), public :: groupListCol
79 integer, allocatable, dimension(:), public :: groupStartCol
80 integer, allocatable, dimension(:), public :: groupListLocal
81 integer, allocatable, dimension(:), public :: groupStartLocal
82 integer, allocatable, dimension(:), public :: nSkipsForAtom
83 integer, allocatable, dimension(:,:), public :: skipsForAtom
84 real(kind=dp), allocatable, dimension(:), public :: mfactRow
85 real(kind=dp), allocatable, dimension(:), public :: mfactCol
86 real(kind=dp), allocatable, dimension(:), public :: mfactLocal
87
88 logical, allocatable, dimension(:) :: simHasAtypeMap
89 #ifdef IS_MPI
90 logical, allocatable, dimension(:) :: simHasAtypeMapTemp
91 #endif
92
93 real(kind=dp), public, dimension(3,3), save :: Hmat, HmatInv
94 real(kind=dp), save :: DangerRcut
95 logical, public, save :: boxIsOrthorhombic
96
97 public :: SimulationSetup
98 public :: getNlocal
99 public :: setBox
100 public :: checkBox
101 public :: SimUsesPBC
102 public :: SimUsesAtomicVirial
103
104 public :: SimUsesDirectionalAtoms
105 public :: SimUsesLennardJones
106 public :: SimUsesElectrostatics
107 public :: SimUsesCharges
108 public :: SimUsesDipoles
109 public :: SimUsesSticky
110 public :: SimUsesStickyPower
111 public :: SimUsesGayBerne
112 public :: SimUsesEAM
113 public :: SimUsesShapes
114 public :: SimUsesFLARB
115 public :: SimUsesRF
116 public :: SimUsesSF
117 public :: SimUsesSP
118 public :: SimUsesBoxDipole
119 public :: SimRequiresPrepairCalc
120 public :: SimRequiresPostpairCalc
121 public :: SimHasAtype
122 public :: SimUsesSC
123 public :: SimUsesMEAM
124 public :: setHmatDangerousRcutValue
125
126 contains
127
128 subroutine SimulationSetup(setThisSim, CnGlobal, CnLocal, c_idents, &
129 CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, &
130 CmolMembership, Cmfact, CnGroups, CglobalGroupMembership, &
131 status)
132
133 type (simtype) :: setThisSim
134 integer, intent(inout) :: CnGlobal, CnLocal
135 integer, dimension(CnLocal),intent(inout) :: c_idents
136
137 integer :: CnLocalExcludes
138 integer, dimension(2,CnLocalExcludes), intent(in) :: CexcludesLocal
139 integer :: CnGlobalExcludes
140 integer, dimension(CnGlobalExcludes), intent(in) :: CexcludesGlobal
141 integer, dimension(CnGlobal),intent(in) :: CmolMembership
142 !! Result status, success = 0, status = -1
143 integer, intent(out) :: status
144 integer :: i, j, me, thisStat, alloc_stat, myNode, id1, id2
145 integer :: ia
146
147 !! mass factors used for molecular cutoffs
148 real ( kind = dp ), dimension(CnLocal) :: Cmfact
149 integer, intent(in):: CnGroups
150 integer, dimension(CnGlobal), intent(in):: CglobalGroupMembership
151 integer :: maxSkipsForAtom, glPointer
152
153 #ifdef IS_MPI
154 integer, allocatable, dimension(:) :: c_idents_Row
155 integer, allocatable, dimension(:) :: c_idents_Col
156 integer :: nAtomsInRow, nGroupsInRow, aid
157 integer :: nAtomsInCol, nGroupsInCol, gid
158 #endif
159
160 simulation_setup_complete = .false.
161 status = 0
162
163 ! copy C struct into fortran type
164
165 nLocal = CnLocal
166 nGlobal = CnGlobal
167 nGroups = CnGroups
168
169 thisSim = setThisSim
170
171 nExcludes_Global = CnGlobalExcludes
172 nExcludes_Local = CnLocalExcludes
173
174 call InitializeForceGlobals(nLocal, thisStat)
175 if (thisStat /= 0) then
176 write(default_error,*) "SimSetup: InitializeForceGlobals error"
177 status = -1
178 return
179 endif
180
181 call InitializeSimGlobals(thisStat)
182 if (thisStat /= 0) then
183 write(default_error,*) "SimSetup: InitializeSimGlobals error"
184 status = -1
185 return
186 endif
187
188 #ifdef IS_MPI
189 ! We can only set up forces if mpiSimulation has been setup.
190 if (.not. isMPISimSet()) then
191 write(default_error,*) "MPI is not set"
192 status = -1
193 return
194 endif
195 nAtomsInRow = getNatomsInRow(plan_atom_row)
196 nAtomsInCol = getNatomsInCol(plan_atom_col)
197 nGroupsInRow = getNgroupsInRow(plan_group_row)
198 nGroupsInCol = getNgroupsInCol(plan_group_col)
199 mynode = getMyNode()
200
201 allocate(c_idents_Row(nAtomsInRow),stat=alloc_stat)
202 if (alloc_stat /= 0 ) then
203 status = -1
204 return
205 endif
206
207 allocate(c_idents_Col(nAtomsInCol),stat=alloc_stat)
208 if (alloc_stat /= 0 ) then
209 status = -1
210 return
211 endif
212
213 call gather(c_idents, c_idents_Row, plan_atom_row)
214 call gather(c_idents, c_idents_Col, plan_atom_col)
215
216 do i = 1, nAtomsInRow
217 me = getFirstMatchingElement(atypes, "c_ident", c_idents_Row(i))
218 atid_Row(i) = me
219 enddo
220
221 do i = 1, nAtomsInCol
222 me = getFirstMatchingElement(atypes, "c_ident", c_idents_Col(i))
223 atid_Col(i) = me
224 enddo
225
226 !! free temporary ident arrays
227 if (allocated(c_idents_Col)) then
228 deallocate(c_idents_Col)
229 end if
230 if (allocated(c_idents_Row)) then
231 deallocate(c_idents_Row)
232 endif
233
234 #endif
235
236 #ifdef IS_MPI
237 allocate(groupStartRow(nGroupsInRow+1),stat=alloc_stat)
238 if (alloc_stat /= 0 ) then
239 status = -1
240 return
241 endif
242 allocate(groupStartCol(nGroupsInCol+1),stat=alloc_stat)
243 if (alloc_stat /= 0 ) then
244 status = -1
245 return
246 endif
247 allocate(groupListRow(nAtomsInRow),stat=alloc_stat)
248 if (alloc_stat /= 0 ) then
249 status = -1
250 return
251 endif
252 allocate(groupListCol(nAtomsInCol),stat=alloc_stat)
253 if (alloc_stat /= 0 ) then
254 status = -1
255 return
256 endif
257 allocate(mfactRow(nAtomsInRow),stat=alloc_stat)
258 if (alloc_stat /= 0 ) then
259 status = -1
260 return
261 endif
262 allocate(mfactCol(nAtomsInCol),stat=alloc_stat)
263 if (alloc_stat /= 0 ) then
264 status = -1
265 return
266 endif
267 allocate(mfactLocal(nLocal),stat=alloc_stat)
268 if (alloc_stat /= 0 ) then
269 status = -1
270 return
271 endif
272
273 glPointer = 1
274
275 do i = 1, nGroupsInRow
276
277 gid = GroupRowToGlobal(i)
278 groupStartRow(i) = glPointer
279
280 do j = 1, nAtomsInRow
281 aid = AtomRowToGlobal(j)
282 if (CglobalGroupMembership(aid) .eq. gid) then
283 groupListRow(glPointer) = j
284 glPointer = glPointer + 1
285 endif
286 enddo
287 enddo
288 groupStartRow(nGroupsInRow+1) = nAtomsInRow + 1
289
290 glPointer = 1
291
292 do i = 1, nGroupsInCol
293
294 gid = GroupColToGlobal(i)
295 groupStartCol(i) = glPointer
296
297 do j = 1, nAtomsInCol
298 aid = AtomColToGlobal(j)
299 if (CglobalGroupMembership(aid) .eq. gid) then
300 groupListCol(glPointer) = j
301 glPointer = glPointer + 1
302 endif
303 enddo
304 enddo
305 groupStartCol(nGroupsInCol+1) = nAtomsInCol + 1
306
307 mfactLocal = Cmfact
308
309 call gather(mfactLocal, mfactRow, plan_atom_row)
310 call gather(mfactLocal, mfactCol, plan_atom_col)
311
312 if (allocated(mfactLocal)) then
313 deallocate(mfactLocal)
314 end if
315 #else
316 allocate(groupStartRow(nGroups+1),stat=alloc_stat)
317 if (alloc_stat /= 0 ) then
318 status = -1
319 return
320 endif
321 allocate(groupStartCol(nGroups+1),stat=alloc_stat)
322 if (alloc_stat /= 0 ) then
323 status = -1
324 return
325 endif
326 allocate(groupListRow(nLocal),stat=alloc_stat)
327 if (alloc_stat /= 0 ) then
328 status = -1
329 return
330 endif
331 allocate(groupListCol(nLocal),stat=alloc_stat)
332 if (alloc_stat /= 0 ) then
333 status = -1
334 return
335 endif
336 allocate(mfactRow(nLocal),stat=alloc_stat)
337 if (alloc_stat /= 0 ) then
338 status = -1
339 return
340 endif
341 allocate(mfactCol(nLocal),stat=alloc_stat)
342 if (alloc_stat /= 0 ) then
343 status = -1
344 return
345 endif
346 allocate(mfactLocal(nLocal),stat=alloc_stat)
347 if (alloc_stat /= 0 ) then
348 status = -1
349 return
350 endif
351
352 glPointer = 1
353 do i = 1, nGroups
354 groupStartRow(i) = glPointer
355 groupStartCol(i) = glPointer
356 do j = 1, nLocal
357 if (CglobalGroupMembership(j) .eq. i) then
358 groupListRow(glPointer) = j
359 groupListCol(glPointer) = j
360 glPointer = glPointer + 1
361 endif
362 enddo
363 enddo
364 groupStartRow(nGroups+1) = nLocal + 1
365 groupStartCol(nGroups+1) = nLocal + 1
366
367 do i = 1, nLocal
368 mfactRow(i) = Cmfact(i)
369 mfactCol(i) = Cmfact(i)
370 end do
371
372 #endif
373
374
375 ! We build the local atid's for both mpi and nonmpi
376 do i = 1, nLocal
377
378 me = getFirstMatchingElement(atypes, "c_ident", c_idents(i))
379 atid(i) = me
380
381 enddo
382
383 do i = 1, nExcludes_Local
384 excludesLocal(1,i) = CexcludesLocal(1,i)
385 excludesLocal(2,i) = CexcludesLocal(2,i)
386 enddo
387
388 #ifdef IS_MPI
389 allocate(nSkipsForAtom(nAtomsInRow), stat=alloc_stat)
390 #else
391 allocate(nSkipsForAtom(nLocal), stat=alloc_stat)
392 #endif
393 if (alloc_stat /= 0 ) then
394 thisStat = -1
395 write(*,*) 'Could not allocate nSkipsForAtom array'
396 return
397 endif
398
399 maxSkipsForAtom = 0
400 #ifdef IS_MPI
401 do j = 1, nAtomsInRow
402 #else
403 do j = 1, nLocal
404 #endif
405 nSkipsForAtom(j) = 0
406 #ifdef IS_MPI
407 id1 = AtomRowToGlobal(j)
408 #else
409 id1 = j
410 #endif
411 do i = 1, nExcludes_Local
412 if (excludesLocal(1,i) .eq. id1 ) then
413 nSkipsForAtom(j) = nSkipsForAtom(j) + 1
414
415 if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
416 maxSkipsForAtom = nSkipsForAtom(j)
417 endif
418 endif
419 if (excludesLocal(2,i) .eq. id1 ) then
420 nSkipsForAtom(j) = nSkipsForAtom(j) + 1
421
422 if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
423 maxSkipsForAtom = nSkipsForAtom(j)
424 endif
425 endif
426 end do
427 enddo
428
429 #ifdef IS_MPI
430 allocate(skipsForAtom(nAtomsInRow, maxSkipsForAtom), stat=alloc_stat)
431 #else
432 allocate(skipsForAtom(nLocal, maxSkipsForAtom), stat=alloc_stat)
433 #endif
434 if (alloc_stat /= 0 ) then
435 write(*,*) 'Could not allocate skipsForAtom array'
436 return
437 endif
438
439 #ifdef IS_MPI
440 do j = 1, nAtomsInRow
441 #else
442 do j = 1, nLocal
443 #endif
444 nSkipsForAtom(j) = 0
445 #ifdef IS_MPI
446 id1 = AtomRowToGlobal(j)
447 #else
448 id1 = j
449 #endif
450 do i = 1, nExcludes_Local
451 if (excludesLocal(1,i) .eq. id1 ) then
452 nSkipsForAtom(j) = nSkipsForAtom(j) + 1
453 ! exclude lists have global ID's so this line is
454 ! the same in MPI and non-MPI
455 id2 = excludesLocal(2,i)
456 skipsForAtom(j, nSkipsForAtom(j)) = id2
457 endif
458 if (excludesLocal(2, i) .eq. id1 ) then
459 nSkipsForAtom(j) = nSkipsForAtom(j) + 1
460 ! exclude lists have global ID's so this line is
461 ! the same in MPI and non-MPI
462 id2 = excludesLocal(1,i)
463 skipsForAtom(j, nSkipsForAtom(j)) = id2
464 endif
465 end do
466 enddo
467
468 do i = 1, nExcludes_Global
469 excludesGlobal(i) = CexcludesGlobal(i)
470 enddo
471
472 do i = 1, nGlobal
473 molMemberShipList(i) = CmolMembership(i)
474 enddo
475
476 call createSimHasAtype(alloc_stat)
477 if (alloc_stat /= 0) then
478 status = -1
479 end if
480
481 if (status == 0) simulation_setup_complete = .true.
482
483 end subroutine SimulationSetup
484
485 subroutine setBox(cHmat, cHmatInv, cBoxIsOrthorhombic)
486 real(kind=dp), dimension(3,3) :: cHmat, cHmatInv
487 integer :: cBoxIsOrthorhombic
488 integer :: smallest, status
489
490 Hmat = cHmat
491 HmatInv = cHmatInv
492 if (cBoxIsOrthorhombic .eq. 0 ) then
493 boxIsOrthorhombic = .false.
494 else
495 boxIsOrthorhombic = .true.
496 endif
497
498 call checkBox()
499 return
500 end subroutine setBox
501
502 subroutine checkBox()
503
504 integer :: i
505 real(kind=dp), dimension(3) :: hx, hy, hz, ax, ay, az, piped
506 character(len = statusMsgSize) :: errMsg
507
508 hx = Hmat(1,:)
509 hy = Hmat(2,:)
510 hz = Hmat(3,:)
511
512 ax = cross_product(hy, hz)
513 ay = cross_product(hx, hz)
514 az = cross_product(hx, hy)
515
516 ax = ax / length(ax)
517 ay = ay / length(ay)
518 az = az / length(az)
519
520 piped(1) = abs(dot_product(ax, hx))
521 piped(2) = abs(dot_product(ay, hy))
522 piped(3) = abs(dot_product(az, hz))
523
524 do i = 1, 3
525 if ((0.5_dp * piped(i)).lt.DangerRcut) then
526 write(errMsg, '(a94,f9.4,a1)') 'One of the dimensions of the Periodic ' &
527 // 'Box is smaller than ' // newline // tab // &
528 'the largest cutoff radius' // &
529 ' (rCut = ', DangerRcut, ')'
530 call handleError("checkBox", errMsg)
531
532 end if
533 enddo
534 return
535 end subroutine checkBox
536
537 function SimUsesPBC() result(doesit)
538 logical :: doesit
539 doesit = thisSim%SIM_uses_PBC
540 end function SimUsesPBC
541
542 function SimUsesAtomicVirial() result(doesit)
543 logical :: doesit
544 doesit = thisSim%SIM_uses_AtomicVirial
545 end function SimUsesAtomicVirial
546
547 function SimUsesDirectionalAtoms() result(doesit)
548 logical :: doesit
549 doesit = thisSim%SIM_uses_dipoles .or. thisSim%SIM_uses_Sticky .or. &
550 thisSim%SIM_uses_StickyPower .or. &
551 thisSim%SIM_uses_GayBerne .or. thisSim%SIM_uses_Shapes
552 end function SimUsesDirectionalAtoms
553
554 function SimUsesLennardJones() result(doesit)
555 logical :: doesit
556 doesit = thisSim%SIM_uses_LennardJones
557 end function SimUsesLennardJones
558
559 function SimUsesElectrostatics() result(doesit)
560 logical :: doesit
561 doesit = thisSim%SIM_uses_Electrostatics
562 end function SimUsesElectrostatics
563
564 function SimUsesCharges() result(doesit)
565 logical :: doesit
566 doesit = thisSim%SIM_uses_Charges
567 end function SimUsesCharges
568
569 function SimUsesDipoles() result(doesit)
570 logical :: doesit
571 doesit = thisSim%SIM_uses_Dipoles
572 end function SimUsesDipoles
573
574 function SimUsesSticky() result(doesit)
575 logical :: doesit
576 doesit = thisSim%SIM_uses_Sticky
577 end function SimUsesSticky
578
579 function SimUsesStickyPower() result(doesit)
580 logical :: doesit
581 doesit = thisSim%SIM_uses_StickyPower
582 end function SimUsesStickyPower
583
584 function SimUsesGayBerne() result(doesit)
585 logical :: doesit
586 doesit = thisSim%SIM_uses_GayBerne
587 end function SimUsesGayBerne
588
589 function SimUsesEAM() result(doesit)
590 logical :: doesit
591 doesit = thisSim%SIM_uses_EAM
592 end function SimUsesEAM
593
594
595 function SimUsesSC() result(doesit)
596 logical :: doesit
597 doesit = thisSim%SIM_uses_SC
598 end function SimUsesSC
599
600 function SimUsesMEAM() result(doesit)
601 logical :: doesit
602 doesit = thisSim%SIM_uses_MEAM
603 end function SimUsesMEAM
604
605
606 function SimUsesShapes() result(doesit)
607 logical :: doesit
608 doesit = thisSim%SIM_uses_Shapes
609 end function SimUsesShapes
610
611 function SimUsesFLARB() result(doesit)
612 logical :: doesit
613 doesit = thisSim%SIM_uses_FLARB
614 end function SimUsesFLARB
615
616 function SimUsesRF() result(doesit)
617 logical :: doesit
618 doesit = thisSim%SIM_uses_RF
619 end function SimUsesRF
620
621 function SimUsesSF() result(doesit)
622 logical :: doesit
623 doesit = thisSim%SIM_uses_SF
624 end function SimUsesSF
625
626 function SimUsesSP() result(doesit)
627 logical :: doesit
628 doesit = thisSim%SIM_uses_SP
629 end function SimUsesSP
630
631 function SimUsesBoxDipole() result(doesit)
632 logical :: doesit
633 doesit = thisSim%SIM_uses_BoxDipole
634 end function SimUsesBoxDipole
635
636 function SimRequiresPrepairCalc() result(doesit)
637 logical :: doesit
638 doesit = thisSim%SIM_uses_EAM .or. thisSim%SIM_uses_SC &
639 .or. thisSim%SIM_uses_MEAM
640 end function SimRequiresPrepairCalc
641
642 function SimRequiresPostpairCalc() result(doesit)
643 logical :: doesit
644 doesit = thisSim%SIM_uses_RF .or. thisSim%SIM_uses_SF &
645 .or. thisSim%SIM_uses_SP .or. thisSim%SIM_uses_BoxDipole
646 end function SimRequiresPostpairCalc
647
648 ! Function returns true if the simulation has this atype
649 function SimHasAtype(thisAtype) result(doesit)
650 logical :: doesit
651 integer :: thisAtype
652 doesit = .false.
653 if(.not.allocated(SimHasAtypeMap)) return
654
655 doesit = SimHasAtypeMap(thisAtype)
656
657 end function SimHasAtype
658
659 subroutine createSimHasAtype(status)
660 integer, intent(out) :: status
661 integer :: alloc_stat
662 integer :: me_i
663 integer :: mpiErrors
664 integer :: nAtypes
665 status = 0
666
667 nAtypes = getSize(atypes)
668 ! Setup logical map for atypes in simulation
669 if (.not.allocated(SimHasAtypeMap)) then
670 allocate(SimHasAtypeMap(nAtypes),stat=alloc_stat)
671 if (alloc_stat /= 0 ) then
672 status = -1
673 return
674 end if
675 SimHasAtypeMap = .false.
676 end if
677
678 ! Loop through the local atoms and grab the atypes present
679 do me_i = 1,nLocal
680 SimHasAtypeMap(atid(me_i)) = .true.
681 end do
682 ! For MPI, we need to know all possible atypes present in
683 ! simulation on all processors. Use LOR operation to set map.
684 #ifdef IS_MPI
685 if (.not.allocated(SimHasAtypeMapTemp)) then
686 allocate(SimHasAtypeMapTemp(nAtypes),stat=alloc_stat)
687 if (alloc_stat /= 0 ) then
688 status = -1
689 return
690 end if
691 end if
692 call mpi_allreduce(SimHasAtypeMap, SimHasAtypeMaptemp, nAtypes, &
693 mpi_logical, MPI_LOR, mpi_comm_world, mpiErrors)
694 simHasAtypeMap = simHasAtypeMapTemp
695 deallocate(simHasAtypeMapTemp)
696 #endif
697 end subroutine createSimHasAtype
698
699 subroutine InitializeSimGlobals(thisStat)
700 integer, intent(out) :: thisStat
701 integer :: alloc_stat
702
703 thisStat = 0
704
705 call FreeSimGlobals()
706
707 allocate(excludesLocal(2,nExcludes_Local), stat=alloc_stat)
708 if (alloc_stat /= 0 ) then
709 thisStat = -1
710 return
711 endif
712
713 allocate(excludesGlobal(nExcludes_Global), stat=alloc_stat)
714 if (alloc_stat /= 0 ) then
715 thisStat = -1
716 return
717 endif
718
719 allocate(molMembershipList(nGlobal), stat=alloc_stat)
720 if (alloc_stat /= 0 ) then
721 thisStat = -1
722 return
723 endif
724
725 end subroutine InitializeSimGlobals
726
727 subroutine FreeSimGlobals()
728
729 !We free in the opposite order in which we allocate in.
730
731 if (allocated(skipsForAtom)) deallocate(skipsForAtom)
732 if (allocated(nSkipsForAtom)) deallocate(nSkipsForAtom)
733 if (allocated(mfactLocal)) deallocate(mfactLocal)
734 if (allocated(mfactCol)) deallocate(mfactCol)
735 if (allocated(mfactRow)) deallocate(mfactRow)
736 if (allocated(groupListCol)) deallocate(groupListCol)
737 if (allocated(groupListRow)) deallocate(groupListRow)
738 if (allocated(groupStartCol)) deallocate(groupStartCol)
739 if (allocated(groupStartRow)) deallocate(groupStartRow)
740 if (allocated(molMembershipList)) deallocate(molMembershipList)
741 if (allocated(excludesGlobal)) deallocate(excludesGlobal)
742 if (allocated(excludesLocal)) deallocate(excludesLocal)
743
744 end subroutine FreeSimGlobals
745
746 pure function getNlocal() result(n)
747 integer :: n
748 n = nLocal
749 end function getNlocal
750
751 subroutine setHmatDangerousRcutValue(dangerWillRobinson)
752 real(kind=dp), intent(in) :: dangerWillRobinson
753 DangerRcut = dangerWillRobinson
754
755 call checkBox()
756
757 return
758 end subroutine setHmatDangerousRcutValue
759
760
761
762 end module simulation