MODULE v3dbc_mod ! !svn $Id: v3dbc_im.F 294 2009-01-09 21:37:26Z arango $ !======================================================================= ! Copyright (c) 2002-2009 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.txt Hernan G. Arango ! !========================================== Alexander F. Shchepetkin === ! ! ! This subroutine sets lateral boundary conditions for total 3D ! ! V-velocity. ! ! ! !======================================================================= ! implicit none PRIVATE PUBLIC :: v3dbc_tile CONTAINS ! !*********************************************************************** SUBROUTINE v3dbc (ng, tile, nout) !*********************************************************************** ! USE mod_param USE mod_ocean USE mod_stepping ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile, nout ! ! Local variable declarations. ! integer :: IminS, ImaxS, JminS, JmaxS integer :: LBi, UBi, LBj, UBj, LBij, UBij ! ! Set horizontal starting and ending indices for automatic private storage ! arrays. ! IminS=BOUNDS(ng)%Istr(tile)-3 ImaxS=BOUNDS(ng)%Iend(tile)+3 JminS=BOUNDS(ng)%Jstr(tile)-3 JmaxS=BOUNDS(ng)%Jend(tile)+3 ! ! Determine array lower and upper bounds in the I- and J-directions. ! LBi=BOUNDS(ng)%LBi(tile) UBi=BOUNDS(ng)%UBi(tile) LBj=BOUNDS(ng)%LBj(tile) UBj=BOUNDS(ng)%UBj(tile) ! ! Set array lower and upper bounds for MIN(I,J)- and MAX(I,J)-directions. ! LBij=BOUNDS(ng)%LBij UBij=BOUNDS(ng)%UBij ! CALL v3dbc_tile (ng, tile, & & LBi, UBi, LBj, UBj, N(ng), & & IminS, ImaxS, JminS, JmaxS, & & nstp(ng), nout, & & OCEAN(ng) % v) RETURN END SUBROUTINE v3dbc ! !*********************************************************************** SUBROUTINE v3dbc_tile (ng, tile, & & LBi, UBi, LBj, UBj, UBk, & & IminS, ImaxS, JminS, JmaxS, & & nstp, nout, & & v) !*********************************************************************** ! USE mod_param USE mod_boundary USE mod_grid USE mod_scalars ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile integer, intent(in) :: LBi, UBi, LBj, UBj, UBk integer, intent(in) :: IminS, ImaxS, JminS, JmaxS integer, intent(in) :: nstp, nout ! real(r8), intent(inout) :: v(LBi:,LBj:,:,:) ! ! Local variable declarations. ! integer :: i, j, k real(r8), parameter :: eps = 1.0E-20_r8 real(r8) :: Ce, Cx, cff, dVde, dVdt, dVdx, tau real(r8), dimension(IminS:ImaxS,JminS:JmaxS) :: grad ! !----------------------------------------------------------------------- ! Set lower and upper tile bounds and staggered variables bounds for ! this horizontal domain partition. Notice that if tile=-1, it will ! set the values for the global grid. !----------------------------------------------------------------------- ! integer :: Istr, IstrR, IstrT, IstrU, Iend, IendR, IendT integer :: Jstr, JstrR, JstrT, JstrV, Jend, JendR, JendT ! Istr =BOUNDS(ng)%Istr (tile) IstrR=BOUNDS(ng)%IstrR(tile) IstrT=BOUNDS(ng)%IstrT(tile) IstrU=BOUNDS(ng)%IstrU(tile) Iend =BOUNDS(ng)%Iend (tile) IendR=BOUNDS(ng)%IendR(tile) IendT=BOUNDS(ng)%IendT(tile) Jstr =BOUNDS(ng)%Jstr (tile) JstrR=BOUNDS(ng)%JstrR(tile) JstrT=BOUNDS(ng)%JstrT(tile) JstrV=BOUNDS(ng)%JstrV(tile) Jend =BOUNDS(ng)%Jend (tile) JendR=BOUNDS(ng)%JendR(tile) JendT=BOUNDS(ng)%JendT(tile) ! !----------------------------------------------------------------------- ! Lateral boundary conditions at the southern edge. !----------------------------------------------------------------------- ! IF (Jstr.eq.1) THEN ! ! Southern edge, closed boundary condition. ! DO k=1,N(ng) DO i=Istr,Iend v(i,Jstr,k,nout)=0.0_r8 END DO END DO END IF ! !----------------------------------------------------------------------- ! Lateral boundary conditions at the northern edge. !----------------------------------------------------------------------- ! IF (Jend.eq.Mm(ng)) THEN ! ! Northern edge, closed boundary condition. ! DO k=1,N(ng) DO i=Istr,Iend v(i,Jend+1,k,nout)=0.0_r8 END DO END DO END IF ! !----------------------------------------------------------------------- ! Lateral boundary conditions at the western edge. !----------------------------------------------------------------------- ! IF (Istr.eq.1) THEN ! ! Western edge, gradient boundary condition. ! DO k=1,N(ng) DO j=JstrV,Jend v(Istr-1,j,k,nout)=v(Istr,j,k,nout) v(Istr-1,j,k,nout)=v(Istr-1,j,k,nout)* & & GRID(ng)%vmask(Istr-1,j) v(Istr-1,j,k,nout)=v(Istr-1,j,k,nout)* & & GRID(ng)%vmask_wet(Istr-1,j) END DO END DO END IF ! !----------------------------------------------------------------------- ! Lateral boundary conditions at the eastern edge. !----------------------------------------------------------------------- ! IF (Iend.eq.Lm(ng)) THEN ! ! Eastern edge, gradient boundary condition. ! DO k=1,N(ng) DO j=JstrV,Jend v(Iend+1,j,k,nout)=v(Iend,j,k,nout) v(Iend+1,j,k,nout)=v(Iend+1,j,k,nout)* & & GRID(ng)%vmask(Iend+1,j) v(Iend+1,j,k,nout)=v(Iend+1,j,k,nout)* & & GRID(ng)%vmask_wet(Iend+1,j) END DO END DO END IF ! !----------------------------------------------------------------------- ! Boundary corners. !----------------------------------------------------------------------- ! IF ((Jstr.eq.1).and.(Istr.eq.1)) THEN DO k=1,N(ng) v(Istr-1,Jstr,k,nout)=0.5_r8*(v(Istr ,Jstr ,k,nout)+ & & v(Istr-1,Jstr+1,k,nout)) END DO END IF IF ((Jstr.eq.1).and.(Iend.eq.Lm(ng))) THEN DO k=1,N(ng) v(Iend+1,Jstr,k,nout)=0.5_r8*(v(Iend ,Jstr ,k,nout)+ & & v(Iend+1,Jstr+1,k,nout)) END DO END IF IF ((Jend.eq.Mm(ng)).and.(Istr.eq.1)) THEN DO k=1,N(ng) v(Istr-1,Jend+1,k,nout)=0.5_r8*(v(Istr-1,Jend ,k,nout)+ & & v(Istr ,Jend+1,k,nout)) END DO END IF IF ((Jend.eq.Mm(ng)).and.(Iend.eq.Lm(ng))) THEN DO k=1,N(ng) v(Iend+1,Jend+1,k,nout)=0.5_r8*(v(Iend+1,Jend ,k,nout)+ & & v(Iend ,Jend+1,k,nout)) END DO END IF RETURN END SUBROUTINE v3dbc_tile END MODULE v3dbc_mod