Skip to content

Commit

Permalink
ww3_diffraction: more on refraction ...
Browse files Browse the repository at this point in the history
  • Loading branch information
aronroland committed Jan 15, 2024
1 parent b71b9b0 commit 099591c
Show file tree
Hide file tree
Showing 5 changed files with 932 additions and 464 deletions.
12 changes: 6 additions & 6 deletions model/src/w3gdatmd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -752,9 +752,9 @@ MODULE W3GDATMD
INTEGER*2, POINTER :: IOBP_LOC(:)
INTEGER*1, POINTER :: IOBDP_LOC(:)
INTEGER*1, POINTER :: IOBPA_LOC(:)
REAL, POINTER :: DIFRM(:)
REAL, POINTER :: DIFRX(:)
REAL, POINTER :: DIFRY(:)
REAL*8, POINTER :: DIFRM(:)
REAL*8, POINTER :: DIFRX(:)
REAL*8, POINTER :: DIFRY(:)
#endif

REAL(8), POINTER :: LEN(:,:),SI(:), IEN(:,:)
Expand Down Expand Up @@ -1116,9 +1116,9 @@ MODULE W3GDATMD
INTEGER*2, POINTER :: IOBP_LOC(:)
INTEGER*1, POINTER :: IOBDP_LOC(:)
INTEGER*1, POINTER :: IOBPA_LOC(:)
REAL, POINTER :: DIFRM(:)
REAL, POINTER :: DIFRX(:)
REAL, POINTER :: DIFRY(:)
REAL*8, POINTER :: DIFRM(:)
REAL*8, POINTER :: DIFRX(:)
REAL*8, POINTER :: DIFRY(:)
#endif

REAL(8), POINTER :: IEN(:,:), LEN(:,:), SI(:)
Expand Down
8 changes: 5 additions & 3 deletions model/src/w3parall.F90
Original file line number Diff line number Diff line change
Expand Up @@ -89,9 +89,11 @@ MODULE W3PARALL
LOGICAL, PARAMETER :: LSLOC = .true.
INTEGER, PARAMETER :: IMEM = 1

REAL, PARAMETER :: ONESIXTH = 1.0d0/6.0d0
REAL, PARAMETER :: ONETHIRD = 1.0d0/3.0d0
REAL, PARAMETER :: ZERO = 0.0d0

REAL*8, PARAMETER :: ONESIXTH = 1.0d0/6.0d0
REAL*8, PARAMETER :: ONETHIRD = 1.0d0/3.0d0
REAL*8, PARAMETER :: ZERO = 0.0d0
REAL*8, PARAMETER :: ONE = 1.d0

REAL*8, PARAMETER :: THR8 = TINY(1.d0)
REAL, PARAMETER :: THR = TINY(1.0)
Expand Down
10 changes: 5 additions & 5 deletions model/src/w3pro3md.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1506,7 +1506,7 @@ END SUBROUTINE W3XYP3
!> @author H. L. Tolman
!> @date 01-Jul-2013
!>
SUBROUTINE W3KTP3 ( ISEA, FACTH, FACK, CTHG0, CG, WN, DW, &
SUBROUTINE W3KTP3 ( ISEA, JSEA, FACTH, FACK, CTHG0, CG, WN, DW, &
DDDX, DDDY, CX, CY, DCXDX, DCXDY, &
DCYDX, DCYDY, DCDX, DCDY, VA, CFLTHMAX, CFLKMAX )
!/
Expand Down Expand Up @@ -1643,7 +1643,7 @@ SUBROUTINE W3KTP3 ( ISEA, FACTH, FACK, CTHG0, CG, WN, DW, &
!/ ------------------------------------------------------------------- /
!/ Parameter list
!/
INTEGER, INTENT(IN) :: ISEA
INTEGER, INTENT(IN) :: ISEA, JSEA
REAL, INTENT(IN) :: FACTH, FACK, CTHG0, CG(0:NK+1), &
WN(0:NK+1), DW, DDDX, DDDY, &
CX, CY, DCXDX, DCXDY, DCYDX, DCYDY
Expand Down Expand Up @@ -1778,8 +1778,8 @@ SUBROUTINE W3KTP3 ( ISEA, FACTH, FACK, CTHG0, CG, WN, DW, &
+ FRK(MAPWN(ISP)) * ( ESIN(ISP)*DDDX - ECOS(ISP)*DDDY )

IF (B_JGS_LDIFR) THEN
VELNOFILT = DIFRM(ISEA)*VELNOFILT-CG(1+(ISP-1)/NTH) &
* (DIFRX(ISEA)*ESIN(ISP)-DIFRY(ISEA)*ECOS(ISP))
VELNOFILT = DIFRM(JSEA)*VELNOFILT-CG(1+(ISP-1)/NTH) &
* (DIFRX(JSEA)*ESIN(ISP)-DIFRY(JSEA)*ECOS(ISP))
ENDIF

!
Expand All @@ -1796,7 +1796,7 @@ SUBROUTINE W3KTP3 ( ISEA, FACTH, FACK, CTHG0, CG, WN, DW, &
! the filtering limits VCFLT to be less than CTMAX
! this modification was proposed by F. Ardhuin 2011/03/06
!
VCFLT(MAPTH2(ISP))=VELNOFILT!SIGN(MIN(ABS(VELNOFILT),CTMAX),VELNOFILT)
VCFLT(MAPTH2(ISP))=SIGN(MIN(ABS(VELNOFILT),CTMAX),VELNOFILT)
END DO
END IF
!
Expand Down
Loading

0 comments on commit 099591c

Please sign in to comment.