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

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines