Skip to content

Commit

Permalink
add cumulative updates
Browse files Browse the repository at this point in the history
  • Loading branch information
mickaelaccensi committed Dec 22, 2023
1 parent 3b14e02 commit ee2b9ed
Showing 1 changed file with 16 additions and 3 deletions.
19 changes: 16 additions & 3 deletions model/src/w3src4md.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2473,7 +2473,7 @@ SUBROUTINE W3SDS4 (A, K, CG, USTAR, USDIR, DEPTH, DAIR, SRHS, &
PB = BRLAMBDA *C
!
END SELECT
!
!############################################################################################"
!
!
!/ ------------------------------------------------------------------- /
Expand All @@ -2485,16 +2485,29 @@ SUBROUTINE W3SDS4 (A, K, CG, USTAR, USDIR, DEPTH, DAIR, SRHS, &
!
IF ( (SSDSC(3).NE.0.) .OR. (SSDSC(5).NE.0.) .OR. (SSDSC(21).NE.0.) ) THEN
DO IK=IK1, NK
RENEWALFREQ = 0.
FACTURB2=-2.*SIG(IK)*K(IK)*FACTURB
DVISC=-4.*SSDSC(21)*K(IK)*K(IK)
C = SIG(IK)/K(IK) ! phase speed
!
IF (SSDSC(3).GT.0 .AND. IK.GT.DIKCUMUL) THEN
! this is the cheap isotropic version
DO IK2=IK1,IK-DIKCUMUL
C2 = SIG(IK2)/K(IK2)
IS2=(IK2-1)*NTH
CUMULWISO=ABS(C2-C)*DSIP(IK2)/(0.5*C2) * DTH
RENEWALFREQ=RENEWALFREQ-CUMULWISO*SUM(BRLAMBDA(IS2+1:IS2+NTH))
END DO
END IF

DO ITH=1,NTH
IS=ITH+(IK-1)*NTH
!
! Computes cumulative effect from Breaking probability
!
RENEWALFREQ = 0.
IF (SSDSC(3).NE.0 .AND. IK.GT.DIKCUMUL) THEN
IF (SSDSC(3).LT.0 .AND. IK.GT.DIKCUMUL) THEN
RENEWALFREQ = 0.
! this is the expensive and largely useless version
DO IK2=IK1,IK-DIKCUMUL
IF (BTH0(IK2).GT.SSDSBR) THEN
IS2=(IK2-1)*NTH
Expand Down

0 comments on commit ee2b9ed

Please sign in to comment.