check2DBnds2x2 Subroutine

subroutine check2DBnds2x2(grid, coordDim, staggerloc, localPet, petCount, ielbnd0, ieubnd0, iloff0, iuoff0, ielbnd1, ieubnd1, iloff1, iuoff1, ielbnd2, ieubnd2, iloff2, iuoff2, ielbnd3, ieubnd3, iloff3, iuoff3, correct, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Grid) :: grid
integer, intent(in) :: coordDim
type(ESMF_StaggerLoc), intent(in) :: staggerloc
integer, intent(in) :: localPet
integer, intent(in) :: petCount
integer, intent(in) :: ielbnd0(:)
integer, intent(in) :: ieubnd0(:)
integer, intent(in) :: iloff0(:)
integer, intent(in) :: iuoff0(:)
integer, intent(in) :: ielbnd1(:)
integer, intent(in) :: ieubnd1(:)
integer, intent(in) :: iloff1(:)
integer, intent(in) :: iuoff1(:)
integer, intent(in) :: ielbnd2(:)
integer, intent(in) :: ieubnd2(:)
integer, intent(in) :: iloff2(:)
integer, intent(in) :: iuoff2(:)
integer, intent(in) :: ielbnd3(:)
integer, intent(in) :: ieubnd3(:)
integer, intent(in) :: iloff3(:)
integer, intent(in) :: iuoff3(:)
logical, intent(inout) :: correct
integer, intent(inout) :: rc

Source Code

subroutine check2DBnds2x2(grid, coordDim, staggerloc, localPet, petCount, &
                          ielbnd0,ieubnd0,iloff0,iuoff0, &
                          ielbnd1,ieubnd1,iloff1,iuoff1, &
                          ielbnd2,ieubnd2,iloff2,iuoff2, &
                          ielbnd3,ieubnd3,iloff3,iuoff3, &
                          correct, rc)

  type (ESMF_Grid) :: grid
  type (ESMF_StaggerLoc),intent(in) :: staggerloc
  integer,intent(in) :: coordDim, localPet, petCount
  integer,intent(in) :: ielbnd0(:),ieubnd0(:),iloff0(:),iuoff0(:)
  integer,intent(in) :: ielbnd1(:),ieubnd1(:),iloff1(:),iuoff1(:)
  integer,intent(in) :: ielbnd2(:),ieubnd2(:),iloff2(:),iuoff2(:)
  integer,intent(in) :: ielbnd3(:),ieubnd3(:),iloff3(:),iuoff3(:)
  logical,intent(inout) :: correct
  integer,intent(inout) :: rc
  
  integer :: localrc
  integer :: elbnd(2),eubnd(2),ecnt(2)
  integer :: clbnd(2),cubnd(2),ccnt(2)
  integer :: tlbnd(2),tubnd(2),tcnt(2)
  real (ESMF_KIND_R8), pointer :: farrayPtr(:,:)

  ! Check if bounds are correct for each DE
  if (petCount .eq. 1) then
      ! Note the order of DE's here is dependant on the ordering
      ! in ESMF_GridCreateNoPeriDim, if that changes then this will
      ! probably have to change also. 

      ! check DE 0
      call ESMF_GridGetCoordBounds(grid, coordDim=coordDim, localDE=0, &
             staggerLoc=staggerloc,                  &
             exclusiveLBound=elbnd, exclusiveUBound=eubnd, exclusiveCount=ecnt,       &
             computationalLBound=clbnd, computationalUBound=cubnd, computationalCount=ccnt,     &
             totalLBound=tlbnd, totalUBound=tubnd, totalCount=tcnt, rc=localrc)
             if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE
!    write(*,*) "0:",clbnd,",",cubnd,correct

     !! set pointer to null
     nullify(farrayPtr)

     !! Get Coord Array From Grid
     call ESMF_GridGetCoord(grid, localDE=0, &
              staggerLoc=staggerloc, coordDim=coordDim, farrayPtr=farrayPtr, rc=localrc)
     if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE
!write(*,*) "H1", rc, correct
     !! Check that output is as expected
     if (.not. associated(farrayPtr)) correct=.false.
     if ((lbound(farrayPtr,1) .ne. tlbnd(1)) .or. (lbound(farrayPtr,2) .ne. tlbnd(2))) correct=.false.
     if ((ubound(farrayPtr,1) .ne. tubnd(1)) .or. (ubound(farrayPtr,2) .ne. tubnd(2))) correct=.false.
!write(*,*) "H2", rc, correct, elbnd(1), ielbnd0(1)-iloff0(1), ":", elbnd(2), ielbnd0(2)-iloff0(2)
     if (elbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
     if (elbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
!write(*,*) "H2.1", rc, correct
     if (eubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
     if (eubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
!write(*,*) "H2.2", rc, correct
     if (ecnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
     if (ecnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.
!write(*,*) "H3", rc, correct
     if (clbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
     if (clbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
     if (cubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
     if (cubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
     if (ccnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
     if (ccnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.
!write(*,*) "H4", rc, correct
     if (tlbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
     if (tlbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
     if (tubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
     if (tubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
     if (tcnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
     if (tcnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.
!write(*,*) "H5", rc, correct


      ! check DE 1
      call ESMF_GridGetCoordBounds(grid2D, coordDim=coordDim, localDE=1, &
             staggerLoc=staggerloc,                  &
             exclusiveLBound=elbnd, exclusiveUBound=eubnd,  exclusiveCount=ecnt,      &
             computationalLBound=clbnd, computationalUBound=cubnd, computationalCount=ccnt,          &
             totalLBound=tlbnd, totalUBound=tubnd, totalCount=tcnt, rc=localrc)
             if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE
!  write(*,*) "1:",clbnd,",",cubnd,correct

     !! set pointer to null
     nullify(farrayPtr)

     !! Get Coord From Grid
     call ESMF_GridGetCoord(grid, localDE=1, &
              staggerLoc=staggerloc, coordDim=coordDim, farrayPtr=farrayPtr, rc=localrc)
     if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE

     !! Check that output is as expected
     if (.not. associated(farrayPtr)) correct=.false.
     if ((lbound(farrayPtr,1) .ne. tlbnd(1)) .or. (lbound(farrayPtr,2) .ne. tlbnd(2))) correct=.false.
     if ((ubound(farrayPtr,1) .ne. tubnd(1)) .or. (ubound(farrayPtr,2) .ne. tubnd(2))) correct=.false.


     if (elbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
     if (elbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
     if (eubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
     if (eubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
     if (ecnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
     if (ecnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

     if (clbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
     if (clbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
     if (cubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
     if (cubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
     if (ccnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
     if (ccnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

     if (tlbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
     if (tlbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
     if (tubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
     if (tubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
     if (tcnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
     if (tcnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

      ! check DE 2
      call ESMF_GridGetCoordBounds(grid, coordDim=coordDim, localDE=2, &
             staggerLoc=staggerloc,                  &
             exclusiveLBound=elbnd, exclusiveUBound=eubnd,  exclusiveCount=ecnt,      &
             computationalLBound=clbnd, computationalUBound=cubnd, computationalCount=ccnt,          &
             totalLBound=tlbnd, totalUBound=tubnd, totalCount=tcnt, rc=localrc)
             if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE
!  write(*,*) "2:",clbnd,",",cubnd,correct
     !! set pointer to null
     nullify(farrayPtr)

     !! Get Coord From Grid
     call ESMF_GridGetCoord(grid, localDE=2, &
              staggerLoc=staggerloc, coordDim=coordDim, farrayPtr=farrayPtr, rc=localrc)
     if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE

     !! Check that output is as expected
     if (.not. associated(farrayPtr)) correct=.false.
     if ((lbound(farrayPtr,1) .ne. tlbnd(1)) .or. (lbound(farrayPtr,2) .ne. tlbnd(2))) correct=.false.
     if ((ubound(farrayPtr,1) .ne. tubnd(1)) .or. (ubound(farrayPtr,2) .ne. tubnd(2))) correct=.false.
 
     if (elbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
     if (elbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
     if (eubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
     if (eubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
     if (ecnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
     if (ecnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.

     if (clbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
     if (clbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
     if (cubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
     if (cubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
     if (ccnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
     if (ccnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.

     if (tlbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
     if (tlbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
     if (tubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
     if (tubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
     if (tcnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
     if (tcnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.

      ! check DE 3
      call ESMF_GridGetCoordBounds(grid, coordDim=coordDim, localDE=3, &
             staggerLoc=staggerloc,                  &
             exclusiveLBound=elbnd, exclusiveUBound=eubnd, exclusiveCount=ecnt,       &
             computationalLBound=clbnd, computationalUBound=cubnd, computationalCount=ccnt,          &
             totalLBound=tlbnd, totalUBound=tubnd, totalCount=tcnt, rc=localrc)
             if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE
!    write(*,*) "3:",clbnd,",",cubnd,correct
     !! set pointer to null
     nullify(farrayPtr)

     !! Get Coord From Grid
     call ESMF_GridGetCoord(grid, localDE=3, &
              staggerLoc=staggerloc, coordDim=coordDim, farrayPtr=farrayPtr, rc=localrc)
     if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE

     !! Check that output is as expected
     if (.not. associated(farrayPtr)) correct=.false.
     if ((lbound(farrayPtr,1) .ne. tlbnd(1)) .or. (lbound(farrayPtr,2) .ne. tlbnd(2))) correct=.false.
     if ((ubound(farrayPtr,1) .ne. tubnd(1)) .or. (ubound(farrayPtr,2) .ne. tubnd(2))) correct=.false.

     if (elbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
     if (elbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
     if (eubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
     if (eubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
     if (ecnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
     if (ecnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.

     if (clbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
     if (clbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
     if (cubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
     if (cubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
     if (ccnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
     if (ccnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.

     if (tlbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
     if (tlbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
     if (tubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
     if (tubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
     if (tcnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
     if (tcnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.


  else  if (petCount .eq. 4) then
      call ESMF_GridGetCoordBounds(grid, coordDim=coordDim, localDE=0, &
             staggerLoc=staggerloc,                  &
             exclusiveLBound=elbnd, exclusiveUBound=eubnd,  exclusiveCount=ecnt,      &
             computationalLBound=clbnd, computationalUBound=cubnd, computationalCount=ccnt,          &
             totalLBound=tlbnd, totalUBound=tubnd, totalCount=tcnt, rc=localrc)
             if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE

      ! set pointer to null
      nullify(farrayPtr)

     ! Get Coord From Grid
     call ESMF_GridGetCoord(grid, localDE=0, &
              staggerLoc=staggerloc, coordDim=coordDim, farrayPtr=farrayPtr, rc=localrc)
     if (localrc .ne. ESMF_SUCCESS) rc=ESMF_FAILURE

     ! Check that output is as expected
     if (.not. associated(farrayPtr)) correct=.false.
     if ((lbound(farrayPtr,1) .ne. tlbnd(1)) .or. (lbound(farrayPtr,2) .ne. tlbnd(2))) correct=.false.
     if ((ubound(farrayPtr,1) .ne. tubnd(1)) .or. (ubound(farrayPtr,2) .ne. tubnd(2))) correct=.false.

     if (localPet .eq. 0) then

        if (elbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
        if (elbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
        if (eubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
        if (eubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
        if (ecnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
        if (ecnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.

        if (clbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
        if (clbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
        if (cubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
        if (cubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
        if (ccnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
        if (ccnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.

        if (tlbnd(1) .ne. ielbnd0(1)-iloff0(1)) correct=.false.
        if (tlbnd(2) .ne. ielbnd0(2)-iloff0(2)) correct=.false.
        if (tubnd(1) .ne. ieubnd0(1)+iuoff0(1)) correct=.false.
        if (tubnd(2) .ne. ieubnd0(2)+iuoff0(2)) correct=.false.
        if (tcnt(1) .ne. ieubnd0(1)-ielbnd0(1)+1+iloff0(1)+iuoff0(1)) correct=.false.
        if (tcnt(2) .ne. ieubnd0(2)-ielbnd0(2)+1+iloff0(2)+iuoff0(2)) correct=.false.


     else if (localPet .eq. 1) then

        if (elbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
        if (elbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
        if (eubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
        if (eubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
        if (ecnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
        if (ecnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

        if (clbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
        if (clbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
        if (cubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
        if (cubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
        if (ccnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
        if (ccnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

        if (tlbnd(1) .ne. ielbnd1(1)-iloff1(1)) correct=.false.
        if (tlbnd(2) .ne. ielbnd1(2)-iloff1(2)) correct=.false.
        if (tubnd(1) .ne. ieubnd1(1)+iuoff1(1)) correct=.false.
        if (tubnd(2) .ne. ieubnd1(2)+iuoff1(2)) correct=.false.
        if (tcnt(1) .ne. ieubnd1(1)-ielbnd1(1)+1+iloff1(1)+iuoff1(1)) correct=.false.
        if (tcnt(2) .ne. ieubnd1(2)-ielbnd1(2)+1+iloff1(2)+iuoff1(2)) correct=.false.

     else if (localPet .eq. 2) then

        if (elbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
        if (elbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
        if (eubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
        if (eubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
        if (ecnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
        if (ecnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.

        if (clbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
        if (clbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
        if (cubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
        if (cubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
        if (ccnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
        if (ccnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.

        if (tlbnd(1) .ne. ielbnd2(1)-iloff2(1)) correct=.false.
        if (tlbnd(2) .ne. ielbnd2(2)-iloff2(2)) correct=.false.
        if (tubnd(1) .ne. ieubnd2(1)+iuoff2(1)) correct=.false.
        if (tubnd(2) .ne. ieubnd2(2)+iuoff2(2)) correct=.false.
        if (tcnt(1) .ne. ieubnd2(1)-ielbnd2(1)+1+iloff2(1)+iuoff2(1)) correct=.false.
        if (tcnt(2) .ne. ieubnd2(2)-ielbnd2(2)+1+iloff2(2)+iuoff2(2)) correct=.false.


     else if (localPet .eq. 3) then

        if (elbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
        if (elbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
        if (eubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
        if (eubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
        if (ecnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
        if (ecnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.

        if (clbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
        if (clbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
        if (cubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
        if (cubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
        if (ccnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
        if (ccnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.

        if (tlbnd(1) .ne. ielbnd3(1)-iloff3(1)) correct=.false.
        if (tlbnd(2) .ne. ielbnd3(2)-iloff3(2)) correct=.false.
        if (tubnd(1) .ne. ieubnd3(1)+iuoff3(1)) correct=.false.
        if (tubnd(2) .ne. ieubnd3(2)+iuoff3(2)) correct=.false.
        if (tcnt(1) .ne. ieubnd3(1)-ielbnd3(1)+1+iloff3(1)+iuoff3(1)) correct=.false.
        if (tcnt(2) .ne. ieubnd3(2)-ielbnd3(2)+1+iloff3(2)+iuoff3(2)) correct=.false.

     endif
  endif
end subroutine check2DBnds2x2