Skip to content

Commit

Permalink
ww3_diffraction: chasing some bugs ...
Browse files Browse the repository at this point in the history
  • Loading branch information
aronroland committed Dec 18, 2023
1 parent d99f8cd commit 9e0a031
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 4 deletions.
11 changes: 9 additions & 2 deletions model/src/w3parall.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1680,6 +1680,13 @@ SUBROUTINE DIFFRA_SIMPLE(VA)
REAL(8) :: DXENG(NPA), DYENG(NPA), DXXEN(NPA), DYYEN(NPA), DXYEN(NPA)
REAL(8) :: DXCGK(NPA), DYCGK(NPA)

if (.not. allocated(difrm) ) then
allocate(difrm(np),difrx(np),difry(np))
difrm = 0.
difrx = 0.
difry = 0.
endif

EWK = 0.d0
ECG = 0.d0
ENG = 0.d0
Expand All @@ -1695,7 +1702,7 @@ SUBROUTINE DIFFRA_SIMPLE(VA)
DO IS = 1, NK
DO ID = 1, NTH
ISP = ID + (IS-1) * NTH
EAD = EAD + VA(ISP,IP) * DDEN(IK) / CG(IS,ISEA)!VA(ISP,IP)/CG(IS,ISEA)*CLATS(ISEA)*DTH*SIG(IS)**2
EAD = EAD + VA(ISP,IP) * DDEN(IS) / CG(IS,ISEA)!VA(ISP,IP)/CG(IS,ISEA)*CLATS(ISEA)*DTH*SIG(IS)**2
ENDDO
ETOT = ETOT + EAD
EWKTOT = EWKTOT + WN(IS,ISEA) * EAD
Expand Down Expand Up @@ -1756,7 +1763,7 @@ SUBROUTINE DIFFRA_SIMPLE(VA)
ELSE
DIFRM(IP) = 1.d0
END IF
WRITE(*,*) 'DIFRM', IP, DIFRM(IP)
!WRITE(*,*) 'DIFRM', IP, DIFRM(IP)
END DO

CALL DIFFERENTIATE_XYDIR(DIFRM, DIFRX, DIFRY)
Expand Down
2 changes: 1 addition & 1 deletion model/src/w3profsmd_pdlib.F90
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,6 @@ MODULE PDLIB_W3PROFSMD
REAL*8, ALLOCATABLE :: FLALL1(:,:,:), KELEM1(:,:,:)
REAL*8, ALLOCATABLE :: FLALL2(:,:,:), KELEM2(:,:,:)
REAL*8, ALLOCATABLE :: FLALL3(:,:,:), KELEM3(:,:,:)
REAL*8, ALLOCATABLE :: DIFRX(:), DIFRY(:), DIFRM(:)
REAL*8, ALLOCATABLE :: NM(:,:,:), DTSI(:)
INTEGER, ALLOCATABLE :: ITER(:)
INTEGER, ALLOCATABLE :: IS0_pdlib(:)
Expand Down Expand Up @@ -703,6 +702,7 @@ SUBROUTINE PDLIB_W3XYPUG ( ISP, FACX, FACY, DTG, VGX, VGY, LCALC )
FSN, FSPSI, FSFCT, FSNIMP, &
GTYPE, UNGTYPE, NBND_MAP, INDEX_MAP
USE YOWNODEPOOL, only: PDLIB_IEN, PDLIB_TRIA
USE W3PARALL, only: DIFRM, DIFRX, DIFRY
USE W3GDATMD, only: IOBP_LOC, IOBPD_LOC, IOBPA_LOC, IOBDP_LOC
USE YOWNODEPOOL, only: iplg, npa
USE W3WDATMD, only: TIME, VA
Expand Down
2 changes: 1 addition & 1 deletion model/src/w3wavemd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -450,7 +450,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
USE PDLIB_W3PROFSMD, only : APPLY_BOUNDARY_CONDITION_VA, COMPUTE_DIFFRACTION
USE PDLIB_W3PROFSMD, only : PDLIB_W3XYPUG, PDLIB_W3XYPUG_BLOCK_IMPLICIT, PDLIB_W3XYPUG_BLOCK_EXPLICIT
USE PDLIB_W3PROFSMD, only : ALL_VA_INTEGRAL_PRINT, ALL_VAOLD_INTEGRAL_PRINT, ALL_FIELD_INTEGRAL_PRINT
USE W3PARALL, only : PDLIB_NSEAL, PDLIB_NSEALM, DIFRX, DIFRY, DIFRM
USE W3PARALL, only : PDLIB_NSEAL, PDLIB_NSEALM
USE yowNodepool, only: npa, iplg, np
#endif
!/
Expand Down

0 comments on commit 9e0a031

Please sign in to comment.