ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/simulation.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/simulation.F90 (file contents):
Revision 1930 by gezelter, Wed Jan 12 22:41:40 2005 UTC vs.
Revision 2402 by chrisfen, Tue Nov 1 19:09:30 2005 UTC

# Line 58 | Line 58 | module simulation
58   #define __FORTRAN90
59   #include "brains/fSimulation.h"
60   #include "UseTheForce/fSwitchingFunction.h"
61 + #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
62  
63    type (simtype), public, save :: thisSim
64  
# Line 82 | Line 83 | module simulation
83    real(kind=dp), allocatable, dimension(:), public :: mfactCol
84    real(kind=dp), allocatable, dimension(:), public :: mfactLocal
85  
86 +  logical, allocatable, dimension(:) :: simHasAtypeMap
87 + #ifdef IS_MPI
88 +  logical, allocatable, dimension(:) :: simHasAtypeMapTemp
89 + #endif
90 +
91    real(kind=dp), public, dimension(3,3), save :: Hmat, HmatInv
92    logical, public, save :: boxIsOrthorhombic
93 <  
93 >
94    public :: SimulationSetup
95    public :: getNlocal
96    public :: setBox
# Line 97 | Line 103 | module simulation
103    public :: SimUsesCharges
104    public :: SimUsesDipoles
105    public :: SimUsesSticky
106 +  public :: SimUsesStickyPower
107    public :: SimUsesGayBerne
108    public :: SimUsesEAM
109    public :: SimUsesShapes
110    public :: SimUsesFLARB
111    public :: SimUsesRF
112 +  public :: SimUsesDampedWolf
113    public :: SimRequiresPrepairCalc
114    public :: SimRequiresPostpairCalc
115 +  public :: SimHasAtype
116  
108  
117   contains
118 <  
118 >
119    subroutine SimulationSetup(setThisSim, CnGlobal, CnLocal, c_idents, &
120         CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, &
121         CmolMembership, Cmfact, CnGroups, CglobalGroupMembership, &
# Line 180 | Line 188 | contains
188      nGroupsInRow = getNgroupsInRow(plan_group_row)
189      nGroupsInCol = getNgroupsInCol(plan_group_col)
190      mynode = getMyNode()
191 <    
191 >
192      allocate(c_idents_Row(nAtomsInRow),stat=alloc_stat)
193      if (alloc_stat /= 0 ) then
194         status = -1
# Line 213 | Line 221 | contains
221      if (allocated(c_idents_Row)) then
222         deallocate(c_idents_Row)
223      endif
224 <  
224 >
225   #endif
226  
227   #ifdef IS_MPI
# Line 252 | Line 260 | contains
260         status = -1
261         return
262      endif
263 <    
263 >
264      glPointer = 1
265  
266      do i = 1, nGroupsInRow
# Line 291 | Line 299 | contains
299  
300      call gather(mfactLocal,      mfactRow,      plan_atom_row)
301      call gather(mfactLocal,      mfactCol,      plan_atom_col)
302 <    
302 >
303      if (allocated(mfactLocal)) then
304         deallocate(mfactLocal)
305      end if
# Line 351 | Line 359 | contains
359         mfactRow(i) = Cmfact(i)
360         mfactCol(i) = Cmfact(i)
361      end do
362 <    
362 >
363   #endif
364  
365  
366 < ! We build the local atid's for both mpi and nonmpi
366 >    ! We build the local atid's for both mpi and nonmpi
367      do i = 1, nLocal
368 <      
368 >
369         me = getFirstMatchingElement(atypes, "c_ident", c_idents(i))
370         atid(i) = me
371 <  
371 >
372      enddo
373  
374      do i = 1, nExcludes_Local
# Line 383 | Line 391 | contains
391   #ifdef IS_MPI
392      do j = 1, nAtomsInRow
393   #else
394 <    do j = 1, nLocal
394 >       do j = 1, nLocal
395   #endif
396 <       nSkipsForAtom(j) = 0
396 >          nSkipsForAtom(j) = 0
397   #ifdef IS_MPI
398 <       id1 = AtomRowToGlobal(j)
398 >          id1 = AtomRowToGlobal(j)
399   #else
400 <       id1 = j
400 >          id1 = j
401   #endif
402 <       do i = 1, nExcludes_Local
403 <          if (excludesLocal(1,i) .eq. id1 ) then
404 <             nSkipsForAtom(j) = nSkipsForAtom(j) + 1
402 >          do i = 1, nExcludes_Local
403 >             if (excludesLocal(1,i) .eq. id1 ) then
404 >                nSkipsForAtom(j) = nSkipsForAtom(j) + 1
405  
406 <             if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
407 <                maxSkipsForAtom = nSkipsForAtom(j)
406 >                if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
407 >                   maxSkipsForAtom = nSkipsForAtom(j)
408 >                endif
409               endif
410 <          endif
411 <          if (excludesLocal(2,i) .eq. id1 ) then
403 <             nSkipsForAtom(j) = nSkipsForAtom(j) + 1
410 >             if (excludesLocal(2,i) .eq. id1 ) then
411 >                nSkipsForAtom(j) = nSkipsForAtom(j) + 1
412  
413 <             if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
414 <                maxSkipsForAtom = nSkipsForAtom(j)
413 >                if (nSkipsForAtom(j) .gt. maxSkipsForAtom) then
414 >                   maxSkipsForAtom = nSkipsForAtom(j)
415 >                endif
416               endif
417 <          endif
418 <       end do
410 <    enddo
417 >          end do
418 >       enddo
419  
420   #ifdef IS_MPI
421 <    allocate(skipsForAtom(nAtomsInRow, maxSkipsForAtom), stat=alloc_stat)
421 >       allocate(skipsForAtom(nAtomsInRow, maxSkipsForAtom), stat=alloc_stat)
422   #else
423 <    allocate(skipsForAtom(nLocal, maxSkipsForAtom), stat=alloc_stat)
423 >       allocate(skipsForAtom(nLocal, maxSkipsForAtom), stat=alloc_stat)
424   #endif
425 <    if (alloc_stat /= 0 ) then
426 <       write(*,*) 'Could not allocate skipsForAtom array'
427 <       return
428 <    endif
425 >       if (alloc_stat /= 0 ) then
426 >          write(*,*) 'Could not allocate skipsForAtom array'
427 >          return
428 >       endif
429  
430   #ifdef IS_MPI
431 <    do j = 1, nAtomsInRow
431 >       do j = 1, nAtomsInRow
432   #else
433 <    do j = 1, nLocal
433 >          do j = 1, nLocal
434   #endif
435 <       nSkipsForAtom(j) = 0
435 >             nSkipsForAtom(j) = 0
436   #ifdef IS_MPI
437 <       id1 = AtomRowToGlobal(j)
437 >             id1 = AtomRowToGlobal(j)
438   #else
439 <       id1 = j
439 >             id1 = j
440   #endif
441 <       do i = 1, nExcludes_Local
442 <          if (excludesLocal(1,i) .eq. id1 ) then
443 <             nSkipsForAtom(j) = nSkipsForAtom(j) + 1
444 <             ! exclude lists have global ID's so this line is
445 <             ! the same in MPI and non-MPI
446 <             id2 = excludesLocal(2,i)
447 <             skipsForAtom(j, nSkipsForAtom(j)) = id2
448 <          endif
449 <          if (excludesLocal(2, i) .eq. id1 ) then
450 <             nSkipsForAtom(j) = nSkipsForAtom(j) + 1
451 <             ! exclude lists have global ID's so this line is
452 <             ! the same in MPI and non-MPI
453 <             id2 = excludesLocal(1,i)
454 <             skipsForAtom(j, nSkipsForAtom(j)) = id2
455 <          endif
456 <       end do
457 <    enddo
450 <    
451 <    do i = 1, nExcludes_Global
452 <       excludesGlobal(i) = CexcludesGlobal(i)
453 <    enddo
454 <
455 <    do i = 1, nGlobal
456 <       molMemberShipList(i) = CmolMembership(i)
457 <    enddo
458 <    
459 <    if (status == 0) simulation_setup_complete = .true.
460 <    
461 <  end subroutine SimulationSetup
462 <  
463 <  subroutine setBox(cHmat, cHmatInv, cBoxIsOrthorhombic)
464 <    real(kind=dp), dimension(3,3) :: cHmat, cHmatInv
465 <    integer :: cBoxIsOrthorhombic
466 <    integer :: smallest, status, i
467 <    
468 <    Hmat = cHmat
469 <    HmatInv = cHmatInv
470 <    if (cBoxIsOrthorhombic .eq. 0 ) then
471 <       boxIsOrthorhombic = .false.
472 <    else
473 <       boxIsOrthorhombic = .true.
474 <    endif
475 <    
476 <    return    
477 <  end subroutine setBox
441 >             do i = 1, nExcludes_Local
442 >                if (excludesLocal(1,i) .eq. id1 ) then
443 >                   nSkipsForAtom(j) = nSkipsForAtom(j) + 1
444 >                   ! exclude lists have global ID's so this line is
445 >                   ! the same in MPI and non-MPI
446 >                   id2 = excludesLocal(2,i)
447 >                   skipsForAtom(j, nSkipsForAtom(j)) = id2
448 >                endif
449 >                if (excludesLocal(2, i) .eq. id1 ) then
450 >                   nSkipsForAtom(j) = nSkipsForAtom(j) + 1
451 >                   ! exclude lists have global ID's so this line is
452 >                   ! the same in MPI and non-MPI
453 >                   id2 = excludesLocal(1,i)
454 >                   skipsForAtom(j, nSkipsForAtom(j)) = id2
455 >                endif
456 >             end do
457 >          enddo
458  
459 <  function getDielect() result(dielect)
460 <    real( kind = dp ) :: dielect
461 <    dielect = thisSim%dielect
482 <  end function getDielect
483 <      
484 <  function SimUsesPBC() result(doesit)
485 <    logical :: doesit
486 <    doesit = thisSim%SIM_uses_PBC
487 <  end function SimUsesPBC
459 >          do i = 1, nExcludes_Global
460 >             excludesGlobal(i) = CexcludesGlobal(i)
461 >          enddo
462  
463 <  function SimUsesDirectionalAtoms() result(doesit)
464 <    logical :: doesit
465 <    doesit = thisSim%SIM_uses_dipoles .or. thisSim%SIM_uses_sticky .or. &
492 <         thisSim%SIM_uses_GayBerne .or. thisSim%SIM_uses_Shapes
493 <  end function SimUsesDirectionalAtoms
463 >          do i = 1, nGlobal
464 >             molMemberShipList(i) = CmolMembership(i)
465 >          enddo
466  
467 <  function SimUsesLennardJones() result(doesit)
468 <    logical :: doesit
469 <    doesit = thisSim%SIM_uses_LennardJones
470 <  end function SimUsesLennardJones
467 >         call createSimHasAtype(alloc_stat)
468 >         if (alloc_stat /= 0) then
469 >            status = -1
470 >         end if
471 >        
472 >         if (status == 0) simulation_setup_complete = .true.
473  
474 <  function SimUsesElectrostatics() result(doesit)
501 <    logical :: doesit
502 <    doesit = thisSim%SIM_uses_Electrostatics
503 <  end function SimUsesElectrostatics
474 >        end subroutine SimulationSetup
475  
476 <  function SimUsesCharges() result(doesit)
477 <    logical :: doesit
478 <    doesit = thisSim%SIM_uses_Charges
479 <  end function SimUsesCharges
476 >        subroutine setBox(cHmat, cHmatInv, cBoxIsOrthorhombic)
477 >          real(kind=dp), dimension(3,3) :: cHmat, cHmatInv
478 >          integer :: cBoxIsOrthorhombic
479 >          integer :: smallest, status, i
480  
481 <  function SimUsesDipoles() result(doesit)
482 <    logical :: doesit
483 <    doesit = thisSim%SIM_uses_Dipoles
484 <  end function SimUsesDipoles
481 >          Hmat = cHmat
482 >          HmatInv = cHmatInv
483 >          if (cBoxIsOrthorhombic .eq. 0 ) then
484 >             boxIsOrthorhombic = .false.
485 >          else
486 >             boxIsOrthorhombic = .true.
487 >          endif
488  
489 <  function SimUsesSticky() result(doesit)
490 <    logical :: doesit
517 <    doesit = thisSim%SIM_uses_Sticky
518 <  end function SimUsesSticky
489 >          return    
490 >        end subroutine setBox
491  
492 <  function SimUsesGayBerne() result(doesit)
493 <    logical :: doesit
494 <    doesit = thisSim%SIM_uses_GayBerne
495 <  end function SimUsesGayBerne
524 <  
525 <  function SimUsesEAM() result(doesit)
526 <    logical :: doesit
527 <    doesit = thisSim%SIM_uses_EAM
528 <  end function SimUsesEAM
492 >        function getDielect() result(dielect)
493 >          real( kind = dp ) :: dielect
494 >          dielect = thisSim%dielect
495 >        end function getDielect
496  
497 <  function SimUsesShapes() result(doesit)
498 <    logical :: doesit
499 <    doesit = thisSim%SIM_uses_Shapes
500 <  end function SimUsesShapes
497 >        function SimUsesPBC() result(doesit)
498 >          logical :: doesit
499 >          doesit = thisSim%SIM_uses_PBC
500 >        end function SimUsesPBC
501  
502 <  function SimUsesFLARB() result(doesit)
503 <    logical :: doesit
504 <    doesit = thisSim%SIM_uses_FLARB
505 <  end function SimUsesFLARB
502 >        function SimUsesDirectionalAtoms() result(doesit)
503 >          logical :: doesit
504 >          doesit = thisSim%SIM_uses_dipoles .or. thisSim%SIM_uses_Sticky .or. &
505 >               thisSim%SIM_uses_StickyPower .or. &
506 >               thisSim%SIM_uses_GayBerne .or. thisSim%SIM_uses_Shapes
507 >        end function SimUsesDirectionalAtoms
508  
509 <  function SimUsesRF() result(doesit)
510 <    logical :: doesit
511 <    doesit = thisSim%SIM_uses_RF
512 <  end function SimUsesRF
509 >        function SimUsesLennardJones() result(doesit)
510 >          logical :: doesit
511 >          doesit = thisSim%SIM_uses_LennardJones
512 >        end function SimUsesLennardJones
513  
514 <  function SimRequiresPrepairCalc() result(doesit)
515 <    logical :: doesit
516 <    doesit = thisSim%SIM_uses_EAM
517 <  end function SimRequiresPrepairCalc
514 >        function SimUsesElectrostatics() result(doesit)
515 >          logical :: doesit
516 >          doesit = thisSim%SIM_uses_Electrostatics
517 >        end function SimUsesElectrostatics
518 >
519 >        function SimUsesCharges() result(doesit)
520 >          logical :: doesit
521 >          doesit = thisSim%SIM_uses_Charges
522 >        end function SimUsesCharges
523  
524 <  function SimRequiresPostpairCalc() result(doesit)
525 <    logical :: doesit
526 <    doesit = thisSim%SIM_uses_RF
527 <  end function SimRequiresPostpairCalc
554 <  
555 <  subroutine InitializeSimGlobals(thisStat)
556 <    integer, intent(out) :: thisStat
557 <    integer :: alloc_stat
558 <    
559 <    thisStat = 0
560 <    
561 <    call FreeSimGlobals()    
562 <    
563 <    allocate(excludesLocal(2,nExcludes_Local), stat=alloc_stat)
564 <    if (alloc_stat /= 0 ) then
565 <       thisStat = -1
566 <       return
567 <    endif
568 <    
569 <    allocate(excludesGlobal(nExcludes_Global), stat=alloc_stat)
570 <    if (alloc_stat /= 0 ) then
571 <       thisStat = -1
572 <       return
573 <    endif
524 >        function SimUsesDipoles() result(doesit)
525 >          logical :: doesit
526 >          doesit = thisSim%SIM_uses_Dipoles
527 >        end function SimUsesDipoles
528  
529 <    allocate(molMembershipList(nGlobal), stat=alloc_stat)
530 <    if (alloc_stat /= 0 ) then
531 <       thisStat = -1
532 <       return
579 <    endif
580 <    
581 <  end subroutine InitializeSimGlobals
582 <  
583 <  subroutine FreeSimGlobals()
584 <    
585 <    !We free in the opposite order in which we allocate in.
529 >        function SimUsesSticky() result(doesit)
530 >          logical :: doesit
531 >          doesit = thisSim%SIM_uses_Sticky
532 >        end function SimUsesSticky
533  
534 <    if (allocated(skipsForAtom)) deallocate(skipsForAtom)
535 <    if (allocated(nSkipsForAtom)) deallocate(nSkipsForAtom)
536 <    if (allocated(mfactLocal)) deallocate(mfactLocal)
537 <    if (allocated(mfactCol)) deallocate(mfactCol)
591 <    if (allocated(mfactRow)) deallocate(mfactRow)
592 <    if (allocated(groupListCol)) deallocate(groupListCol)    
593 <    if (allocated(groupListRow)) deallocate(groupListRow)    
594 <    if (allocated(groupStartCol)) deallocate(groupStartCol)
595 <    if (allocated(groupStartRow)) deallocate(groupStartRow)    
596 <    if (allocated(molMembershipList)) deallocate(molMembershipList)    
597 <    if (allocated(excludesGlobal)) deallocate(excludesGlobal)
598 <    if (allocated(excludesLocal)) deallocate(excludesLocal)
599 <    
600 <  end subroutine FreeSimGlobals
601 <  
602 <  pure function getNlocal() result(n)
603 <    integer :: n
604 <    n = nLocal
605 <  end function getNlocal
606 <  
607 <  
608 < end module simulation
534 >        function SimUsesStickyPower() result(doesit)
535 >          logical :: doesit
536 >          doesit = thisSim%SIM_uses_StickyPower
537 >        end function SimUsesStickyPower
538  
539 +        function SimUsesGayBerne() result(doesit)
540 +          logical :: doesit
541 +          doesit = thisSim%SIM_uses_GayBerne
542 +        end function SimUsesGayBerne
543  
544 < subroutine setFortranSim(setThisSim, CnGlobal, CnLocal, c_idents, &
545 <       CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, &
546 <       CmolMembership, Cmfact, CnGroups, CglobalGroupMembership, &
547 <       status)
615 <       use definitions, ONLY : dp    
616 <       use simulation
617 <    
618 <    type (simtype) :: setThisSim
619 <    integer, intent(inout) :: CnGlobal, CnLocal
620 <    integer, dimension(CnLocal),intent(inout) :: c_idents
544 >        function SimUsesEAM() result(doesit)
545 >          logical :: doesit
546 >          doesit = thisSim%SIM_uses_EAM
547 >        end function SimUsesEAM
548  
549 <    integer :: CnLocalExcludes
550 <    integer, dimension(2,CnLocalExcludes), intent(inout) :: CexcludesLocal
551 <    integer :: CnGlobalExcludes
552 <    integer, dimension(CnGlobalExcludes), intent(inout) :: CexcludesGlobal
553 <    integer, dimension(CnGlobal),intent(inout) :: CmolMembership
554 <    !!  Result status, success = 0, status = -1
555 <    integer, intent(inout) :: status
556 <    
557 <    !! mass factors used for molecular cutoffs
558 <    real ( kind = dp ), dimension(CnLocal) :: Cmfact
559 <    integer, intent(in):: CnGroups
560 <    integer, dimension(CnGlobal), intent(inout):: CglobalGroupMembership
561 <    
562 <    call SimulationSetup(setThisSim, CnGlobal, CnLocal, c_idents, &
563 <       CnLocalExcludes, CexcludesLocal, CnGlobalExcludes, CexcludesGlobal, &
564 <       CmolMembership, Cmfact, CnGroups, CglobalGroupMembership, &
565 <       status)
566 < end subroutine setFortranSim
567 <
568 < subroutine setFortranBox(cHmat, cHmatInv, cBoxIsOrthorhombic)
569 <    use simulation, only : setBox
570 <    use definitions, ONLY : dp
571 <    real(kind=dp), dimension(3,3) :: cHmat, cHmatInv
572 <    integer :: cBoxIsOrthorhombic
573 <  
574 <   call setBox(cHmat, cHmatInv, cBoxIsOrthorhombic)
575 <    
576 < end subroutine setFortranBox
549 >        function SimUsesShapes() result(doesit)
550 >          logical :: doesit
551 >          doesit = thisSim%SIM_uses_Shapes
552 >        end function SimUsesShapes
553 >
554 >        function SimUsesFLARB() result(doesit)
555 >          logical :: doesit
556 >          doesit = thisSim%SIM_uses_FLARB
557 >        end function SimUsesFLARB
558 >
559 >        function SimUsesRF() result(doesit)
560 >          logical :: doesit
561 >          doesit = thisSim%SIM_uses_RF
562 >        end function SimUsesRF
563 >
564 >        function SimUsesDampedWolf() result(doesit)
565 >          logical :: doesit
566 >          doesit = thisSim%SIM_uses_DampedWolf
567 >        end function SimUsesDampedWolf
568 >
569 >        function SimRequiresPrepairCalc() result(doesit)
570 >          logical :: doesit
571 >          doesit = thisSim%SIM_uses_EAM
572 >        end function SimRequiresPrepairCalc
573 >        
574 >        function SimRequiresPostpairCalc() result(doesit)
575 >          logical :: doesit
576 >          doesit = thisSim%SIM_uses_RF .or. thisSim%SIM_uses_DampedWolf
577 >        end function SimRequiresPostpairCalc
578 >
579 >        ! Function returns true if the simulation has this atype
580 >        function SimHasAtype(thisAtype) result(doesit)
581 >          logical :: doesit
582 >          integer :: thisAtype
583 >          doesit = .false.
584 >          if(.not.allocated(SimHasAtypeMap)) return
585 >
586 >          doesit = SimHasAtypeMap(thisAtype)
587 >            
588 >        end function SimHasAtype
589 >
590 >        subroutine createSimHasAtype(status)
591 >          integer, intent(out) :: status
592 >          integer :: alloc_stat
593 >          integer :: me_i
594 >          integer :: mpiErrors
595 >          integer :: nAtypes
596 >          status = 0
597 >
598 >          nAtypes = getSize(atypes)
599 >          ! Setup logical map for atypes in simulation
600 >          if (.not.allocated(SimHasAtypeMap)) then
601 >             allocate(SimHasAtypeMap(nAtypes),stat=alloc_stat)
602 >             if (alloc_stat /= 0 ) then
603 >                status = -1
604 >                return
605 >             end if
606 >             SimHasAtypeMap = .false.
607 >          end if
608 >          
609 >          ! Loop through the local atoms and grab the atypes present        
610 >          do me_i = 1,nLocal
611 >             SimHasAtypeMap(atid(me_i)) = .true.
612 >          end do
613 >          ! For MPI, we need to know all possible atypes present in
614 >          ! simulation on all processors. Use LOR operation to set map.
615 > #ifdef IS_MPI
616 >          if (.not.allocated(SimHasAtypeMapTemp)) then
617 >             allocate(SimHasAtypeMapTemp(nAtypes),stat=alloc_stat)
618 >             if (alloc_stat /= 0 ) then
619 >                status = -1
620 >                return
621 >             end if
622 >          end if
623 >          call mpi_allreduce(SimHasAtypeMap, SimHasAtypeMaptemp, nAtypes, &
624 >               mpi_logical, MPI_LOR, mpi_comm_world, mpiErrors)
625 >          simHasAtypeMap = simHasAtypeMapTemp
626 >          deallocate(simHasAtypeMapTemp)
627 > #endif          
628 >        end subroutine createSimHasAtype
629 >        
630 >       subroutine InitializeSimGlobals(thisStat)
631 >          integer, intent(out) :: thisStat
632 >          integer :: alloc_stat
633 >
634 >          thisStat = 0
635 >
636 >          call FreeSimGlobals()    
637 >
638 >          allocate(excludesLocal(2,nExcludes_Local), stat=alloc_stat)
639 >          if (alloc_stat /= 0 ) then
640 >             thisStat = -1
641 >             return
642 >          endif
643 >
644 >          allocate(excludesGlobal(nExcludes_Global), stat=alloc_stat)
645 >          if (alloc_stat /= 0 ) then
646 >             thisStat = -1
647 >             return
648 >          endif
649 >
650 >          allocate(molMembershipList(nGlobal), stat=alloc_stat)
651 >          if (alloc_stat /= 0 ) then
652 >             thisStat = -1
653 >             return
654 >          endif
655 >
656 >        end subroutine InitializeSimGlobals
657 >
658 >        subroutine FreeSimGlobals()
659 >
660 >          !We free in the opposite order in which we allocate in.
661 >
662 >          if (allocated(skipsForAtom)) deallocate(skipsForAtom)
663 >          if (allocated(nSkipsForAtom)) deallocate(nSkipsForAtom)
664 >          if (allocated(mfactLocal)) deallocate(mfactLocal)
665 >          if (allocated(mfactCol)) deallocate(mfactCol)
666 >          if (allocated(mfactRow)) deallocate(mfactRow)
667 >          if (allocated(groupListCol)) deallocate(groupListCol)    
668 >          if (allocated(groupListRow)) deallocate(groupListRow)    
669 >          if (allocated(groupStartCol)) deallocate(groupStartCol)
670 >          if (allocated(groupStartRow)) deallocate(groupStartRow)    
671 >          if (allocated(molMembershipList)) deallocate(molMembershipList)    
672 >          if (allocated(excludesGlobal)) deallocate(excludesGlobal)
673 >          if (allocated(excludesLocal)) deallocate(excludesLocal)
674 >
675 >        end subroutine FreeSimGlobals
676 >
677 >        pure function getNlocal() result(n)
678 >          integer :: n
679 >          n = nLocal
680 >        end function getNlocal
681 >
682 >
683 >
684 >
685 >
686 >      end module simulation

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines