Skip to content

Commit

Permalink
Restore peak_ang and stress_gc
Browse files Browse the repository at this point in the history
  • Loading branch information
awnawab committed Mar 27, 2024
1 parent eb4ae08 commit 9085bd3
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 11 deletions.
10 changes: 6 additions & 4 deletions src/ecwam/peak_ang.F90
Original file line number Diff line number Diff line change
Expand Up @@ -75,8 +75,9 @@ SUBROUTINE PEAK_ANG(KIJS, KIJL, FL1, XNU, SIG_TH)
!*** 1. DETERMINE L-H SPECTRAL WIDTH OF THE 2-D SPECTRUM.
! ---------------------------------------------------

ZEPSILON = 10._JWRB*EPSILON(ZEPSILON)
NSH = 1 + INT(LOG(1.5_JWRB)/LOG(FRATIO))
ZEPSILON=10._JWRB*EPSILON(ZEPSILON)

NSH = 1 + INT(LOG(1.5_JWRB)/LOG(FRATIO))

DO IJ=KIJS,KIJL
SUM0(IJ)= ZEPSILON
Expand Down Expand Up @@ -147,9 +148,10 @@ SUBROUTINE PEAK_ANG(KIJS, KIJL, FL1, XNU, SIG_TH)
DO IJ=KIJS,KIJL
MMSTART = MAX(1,MMAX(IJ)-NSH)
MMSTOP = MIN(NFRE,MMAX(IJ)+NSH)

SUM_S(IJ) = 0._JWRB
SUM_C(IJ) = ZEPSILON
DO M=MMSTART,MMSTOP
SUM_S(IJ) = 0._JWRB
SUM_C(IJ) = ZEPSILON
DO K=1,NANG
SUM_S(IJ) = SUM_S(IJ) +SINTH(K)*FL1(IJ,K,M)
SUM_C(IJ) = SUM_C(IJ) +COSTH(K)*FL1(IJ,K,M)
Expand Down
13 changes: 6 additions & 7 deletions src/ecwam/stress_gc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ REAL(KIND=JWRB) FUNCTION STRESS_GC(ANG_GC, USTAR, Z0, Z0MIN, HALP, RNFAC)
REAL(KIND=JWRB) :: CONST, ZN
REAL(KIND=JWRB) :: GAMNORMA ! RENORMALISATION FACTOR OF THE GROWTH RATE
REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
REAL(KIND=JWRB) :: GAM_W
REAL(KIND=JWRB), DIMENSION(NWAV_GC) :: GAM_W

! INCLUDE FUNCTIONS FROM GRAVITY-CAPILLARY DISPERSION REALTIONS
#include "gc_dispersion.h"
Expand Down Expand Up @@ -96,12 +96,12 @@ REAL(KIND=JWRB) FUNCTION STRESS_GC(ANG_GC, USTAR, Z0, Z0MIN, HALP, RNFAC)
ZLOG = XLOG - LOG(XLAMBDA)
ZLOG = MIN(ZLOG, 0.0_JWRB)
ZLOG2X = ZLOG*ZLOG*X
GAM_W(I)= ZLOG2X*ZLOG2X*EXP(XLOG)*OM3GMKM_GC(I)
ENDDO

GAM_W = ZLOG2X*ZLOG2X*EXP(XLOG)*OM3GMKM_GC(NS)
ZN = CONST*XKMSQRTVGOC2_GC(NS)*GAM_W
ZN = CONST*XKMSQRTVGOC2_GC(NS)*GAM_W(NS)
GAMNORMA = (1.0_JWRB + RN1_RN*ZN)/(1.0_JWRB + ZN)
TAUWCG = GAM_W * DELKCC_GC_NS(NS) * OMXKM3_GC(NS) * GAMNORMA
TAUWCG = GAM_W(NS) * DELKCC_GC_NS(NS) * OMXKM3_GC(NS) * GAMNORMA
DO I = NS+1, NWAV_GC
! ANALYTICAL FORM INERTIAL SUB RANGE F(k) = k**(-4)*BB
! BB = HALP * C2OSQRTVG_GC(NS)*SQRT(VG_GC(I))/C_GC(I)**2
Expand All @@ -112,10 +112,9 @@ REAL(KIND=JWRB) FUNCTION STRESS_GC(ANG_GC, USTAR, Z0, Z0MIN, HALP, RNFAC)
! Tauwcg : integral of omega * gammma_wam * F(k) k dk
! It should be done in vector form with actual directional spreading information
! It simplified here by using the ANG_GC factor.
GAM_W = ZLOG2X*ZLOG2X*EXP(XLOG)*OM3GMKM_GC(I)
ZN = CONST*XKMSQRTVGOC2_GC(I)*GAM_W
ZN = CONST*XKMSQRTVGOC2_GC(I)*GAM_W(I)
GAMNORMA = (1.0_JWRB + RN1_RN*ZN)/(1.0_JWRB + ZN)
TAUWCG = TAUWCG + GAM_W * DELKCC_OMXKM3_GC(I) * GAMNORMA
TAUWCG = TAUWCG + GAM_W(I) * DELKCC_OMXKM3_GC(I) * GAMNORMA
ENDDO
STRESS_GC = MAX(ZABHRC * TAUWCG, TAUWCG_MIN)

Expand Down

0 comments on commit 9085bd3

Please sign in to comment.