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

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines