MODULE ini_hmixcoef_mod ! ! svn $Id: ini_hmixcoef.F 412 2009-12-03 20:46:03Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2009 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.txt ! !======================================================================= ! ! ! This routine initializes horizontal mixing coefficients arrays ! ! according to the model flag. ! ! ! ! WARNING: All biharmonic coefficients are assumed to have the ! ! square root taken and have m^2 s^-1/2 units. This ! ! will allow multiplying the biharmonic coefficient ! ! to harmonic operator. ! ! ! !======================================================================= ! implicit none PRIVATE PUBLIC :: ini_hmixcoef CONTAINS ! !*********************************************************************** SUBROUTINE ini_hmixcoef (ng, tile, model) !*********************************************************************** ! USE mod_param USE mod_grid USE mod_mixing USE mod_ncparam USE mod_scalars ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile, model ! ! 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 ini_hmixcoef_tile (ng, tile, model, & & LBi, UBi, LBj, UBj, & & IminS, ImaxS, JminS, JmaxS, & & MIXING(ng) % diff2, & & tnu2(:,ng), tnu4(:,ng), & & visc2(ng), visc4(ng)) RETURN END SUBROUTINE ini_hmixcoef ! !*********************************************************************** SUBROUTINE ini_hmixcoef_tile (ng, tile, model, & & LBi, UBi, LBj, UBj, & & IminS, ImaxS, JminS, JmaxS, & & diff2, & & diffusion2, diffusion4, & & viscosity2, viscosity4) !*********************************************************************** ! USE mod_param USE mod_scalars ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile, model integer, intent(in) :: LBi, UBi, LBj, UBj integer, intent(in) :: IminS, ImaxS, JminS, JmaxS ! real(r8), intent(out) :: diffusion2(:), diffusion4(:) real(r8), intent(out) :: viscosity2, viscosity4 ! real(r8), intent(inout) :: diff2(LBi:,LBj:,:) ! ! Local variable declarations. ! integer :: Imin, Imax, Jmin, Jmax integer :: i, j integer :: itrc ! !----------------------------------------------------------------------- ! Set horizontal, constant, mixing coefficient according to model flag. !----------------------------------------------------------------------- ! IF (model.eq.iNLM) THEN viscosity2=nl_visc2(ng) viscosity4=nl_visc4(ng) DO itrc=1,NT(ng) diffusion2(itrc)=nl_tnu2(itrc,ng) diffusion4(itrc)=nl_tnu4(itrc,ng) END DO END IF ! !----------------------------------------------------------------------- ! Initialize horizontal mixing arrays to constant mixing coefficient. !----------------------------------------------------------------------- ! Imin=BOUNDS(ng)%LBi(tile) Imax=BOUNDS(ng)%UBi(tile) Jmin=BOUNDS(ng)%LBj(tile) Jmax=BOUNDS(ng)%UBj(tile) ! RETURN END SUBROUTINE ini_hmixcoef_tile END MODULE ini_hmixcoef_mod