!> @file !> @brief Subroutine that computes U and V wind stresses. !> !> This routine computes surface layer U and V !> wind component stresses using K theory as presented !> in section 8.4 of "Numerical prediction and dynamic !> meteorology" by Haltiner and Williams (1980, John Wiley !> & Sons). !> !> @param[out] TAUX Suface layer U component wind stress. !> @param[out] TAUY Suface layer V component wind stress. !> !> ### Program history log: !> Date | Programmer | Comments !> -----|------------|--------- !> 1993-09-01 | Russ Treadon | Initial !> 1998-06-11 | T Black | Convesion from 1-D to 2-D !> 2000-01-04 | Jim Tuccillo | MPI Version !> 2001-10-25 | H Chuang | Modified to process hybrid output !> 2002-01-15 | Mike Baldwin | WRF Version, output is on mass-points !> 2005-02-23 | H Chuang | Compute stress for NMM on wind points !> 2005-07-07 | Binbin Zhou | Add RSM stress for A Grid !> 2021-07-26 | W Meng | Restrict computation from undefined grids !> 2021-09-02 | Bo Cui | Decompose UPP in X direction !> !> @author Russ Treadon W/NP2 @date 1993-09-01 SUBROUTINE CALTAU(TAUX,TAUY) ! ! use vrbls3d, only: zint, pmid, q, t, uh, vh, el_pbl, zmid use vrbls2d, only: z0, uz0, vz0 use masks, only: lmh use params_mod, only: d00, d50, h1, d608, rd, d25 use ctlblk_mod, only: jsta_2l, jend_2u, lm, jsta, jend, spval, jsta_m,& jm, im, jend_m, ista, iend, ista_m, iend_m, ista_2l, iend_2u use gridspec_mod, only: gridtype implicit none ! ! DECLARE VARIABLES. INTEGER, dimension(4) :: KK(4) INTEGER, dimension(jm) :: ive, ivw REAL, dimension(ista:iend,jsta:jend), intent(inout) :: TAUX, TAUY REAL, ALLOCATABLE :: EL(:,:,:) REAL, dimension(ista:iend,jsta:jend) :: EGRIDU,EGRIDV,EGRID4,EGRID5, EL0 REAL UZ0V,VZ0V CHARACTER*1 AGRID integer I,J,LMHK,IE,IW,ii,jj real DZ,RDZ,RSFC,TV,RHO,ULMH,VLMH,DELUDZ,DELVDZ,ELSQR,ZINT1, & ZINT2,Z0V,PSFC,TVV,QVV,ELV,ELV1,ELV2 ! !******************************************************************** ! START CALTAU HERE. ! ALLOCATE (EL(ISTA_2L:IEND_2U,JSTA_2L:JEND_2U,LM)) ! ! COMPUTE MASTER LENGTH SCALE. ! ! CALL CLMAX(EL0,EGRIDU,EGRIDV,EGRID4,EGRID5) ! CALL MIXLEN(EL0,EL) ! ! INITIALIZE OUTPUT AND WORK ARRAY TO ZERO. ! DO J=JSTA,JEND DO I=ISTA,IEND EGRIDU(I,J) = D00 EGRIDV(I,J) = D00 TAUX(I,J) = SPVAL TAUY(I,J) = SPVAL ENDDO ENDDO ! ! COMPUTE SURFACE LAYER U AND V WIND STRESSES. ! ! ASSUME THAT U AND V HAVE UPDATED HALOS ! IF(GRIDTYPE == 'A')THEN CALL CLMAX(EL0,EGRIDU,EGRIDV,EGRID4,EGRID5) CALL MIXLEN(EL0,EL) DO J=JSTA,JEND DO I=ISTA,IEND ! LMHK = NINT(LMH(I,J)) IF(EL(I,J,LMHK-1)1.0e2)print*,'Debug TAUX= ',i,j, & ! ELV,ULMH,UZ0(I,J),ZMID(I,J,LMHK),Z0(I,J),RDZ,TAUX(I,J),zint(i,j,lm+1) TAUY(I,J) = RHO*ELSQR*DELVDZ*DELVDZ END DO END DO END IF ! DEALLOCATE(EL) ! END OF ROUTINE. ! RETURN END