Skip to content

Commit

Permalink
Merge pull request #91 from jili2016/master
Browse files Browse the repository at this point in the history
update for land/sea mask on HYCOM writing out
  • Loading branch information
StevePny authored Jul 27, 2017
2 parents cb58b27 + 3da7c3a commit a0217bd
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 12 deletions.
18 changes: 9 additions & 9 deletions src/model_specific/hycom/common_hycom.f90
Original file line number Diff line number Diff line change
Expand Up @@ -419,52 +419,52 @@ SUBROUTINE write_restart(outfile,v3d,v2d)
do k=1,nlev
do j=1,nlat
do i=1,nlon
if (v3d(i,j,k,iv3d_t) < min_t .and. pmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_t) < min_t) then
WRITE(6,*) "WARNING: Bad temp value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_t)
v3d(i,j,k,iv3d_t) = min_t
endif


if (v3d(i,j,k,iv3d_t) > max_t .and. pmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_t) > max_t) then
WRITE(6,*) "WARNING: Bad temp value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_t)
v3d(i,j,k,iv3d_t) = max_t
endif


if (v3d(i,j,k,iv3d_s) < min_s .and. pmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_s) < min_s) then
WRITE(6,*) "WARNING: Bad salt value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_s)
v3d(i,j,k,iv3d_s) = min_s
endif


if (v3d(i,j,k,iv3d_s) > max_s .and. pmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_s) > max_s) then
WRITE(6,*) "WARNING: Bad salt value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_s)
v3d(i,j,k,iv3d_s) = max_s
endif

if (v3d(i,j,k,iv3d_u) < min_uv .and. umsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_u) < min_uv) then
WRITE(6,*) "WARNING: Bad u-vel value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_u)
v3d(i,j,k,iv3d_u) = min_uv
endif

if (v3d(i,j,k,iv3d_u) > max_uv .and. umsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_u) > max_uv) then
WRITE(6,*) "WARNING: Bad u-vel value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_u)
v3d(i,j,k,iv3d_u) = max_uv
endif

if (v3d(i,j,k,iv3d_v) < min_uv .and. vmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_v) < min_uv) then
WRITE(6,*) "WARNING: Bad v-vel value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_v)
v3d(i,j,k,iv3d_v) = min_uv
endif

if (v3d(i,j,k,iv3d_v) > max_uv .and. vmsk(i,j) == 1) then
if (v3d(i,j,k,iv3d_v) > max_uv) then
WRITE(6,*) "WARNING: Bad v-vel value in analysis output:"
WRITE(6,*) "v3d(",i,",",j,",",k,") = ", v3d(i,j,k,iv3d_v)
v3d(i,j,k,iv3d_v) = max_uv
Expand All @@ -481,7 +481,7 @@ SUBROUTINE write_restart(outfile,v3d,v2d)

WRITE(6,*) "common_hycom.f90::write_restart:: calling write_hycom..."
!JILI HYCOM archive file output
CALL put_hycom(infile_a,infile_b,v3d,v2d,pmsk,umsk,vmsk)
CALL put_hycom(infile_a,infile_b,v3d,v2d)
WRITE(6,*) "common_hycom.f90::write_restart:: Finished calling write_hycom."

END SUBROUTINE write_restart
Expand Down
14 changes: 11 additions & 3 deletions src/model_specific/hycom/hycom_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -475,7 +475,7 @@ SUBROUTINE get_hycom(file_in_a,file_in_b,v3d,v2d)
REAL(r_size), INTENT(OUT) :: v2d(nlon,nlat,nv2d)
INTEGER :: k,n,nrec
INTEGER, PARAMETER :: fid=12
INTEGER, PARAMETER, DIMENSION(nv2d) :: input_order_2d = (/ 1,2,3 /),output_order_2d = (/ 1,2,3 /)
INTEGER, PARAMETER, DIMENSION(nv2d) :: input_order_2d = (/ 1,2,3 /),output_order_2d = (/ 1,2,3 /)
INTEGER, PARAMETER, DIMENSION(nv3d) :: input_order_3d = (/ 1,2,3,4,5 /),output_order_3d = (/ 1,2,5,3,4/)

character cline*80
Expand Down Expand Up @@ -1112,7 +1112,7 @@ subroutine check_grid_ab(var_name_a,var_name_b,hmina,hminb,hmaxa,hmaxb)
end subroutine check_grid_ab


SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d)

!
! --- hycom output
Expand All @@ -1125,7 +1125,7 @@ SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
REAL(r_sngl),DIMENSION(:,:,:) :: v2d !(nlon,nlat,nv2d)
INTEGER :: k,n,nrec
INTEGER, PARAMETER :: fid=12
INTEGER, PARAMETER, DIMENSION(nv2d) :: input_order_2d = (/ 1,2,3/),output_order_2d = (/ 1,2,3 /)
INTEGER, PARAMETER, DIMENSION(nv2d) :: input_order_2d = (/ 1,2,3/),output_order_2d = (/ 1,2,3/)
INTEGER, PARAMETER, DIMENSION(nv3d) :: input_order_3d = (/ 1,2,3,4,5/),output_order_3d = (/ 1,2,5,3,4/)
character cline*80
character ctitle(4)*80
Expand All @@ -1143,6 +1143,10 @@ SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
! JILI skip ZAIOST
!CALL ZAIOST

mskp=0
msku=0
mskv=0


! Please make sure the variables in "a" file are in the right order
! Check "b" file to make sure
Expand Down Expand Up @@ -1175,6 +1179,8 @@ SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
read(110,'(a)') cline
i= index(cline,'=')
read (cline(i+1:),*) nstep,time(1),layer,thbase,hminb,hmaxb
where (abs(dummy_2d-hycom_undef) > hycom_eps) mskp=1


CALL ZAIOWR(dummy_2d,mskp,.true.,xmin,xmax,24,.false.)
write(24,117) 'montg1 ',nstep,time(1),layer,thbase,xmin,xmax
Expand Down Expand Up @@ -1266,6 +1272,7 @@ SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
read(110,'(a)') cline
i= index(cline,'=')
read (cline(i+1:),*) nstep,time(1),layer,thbase,hminb,hmaxb
where (abs(dummy_2d-hycom_undef) > hycom_eps) msku=1

CALL ZAIOWR(dummy_2d,msku,.true.,xmin,xmax,24,.false.)
write(24,117) 'umix ',nstep,time(1),layer,thbase,xmin,xmax
Expand All @@ -1275,6 +1282,7 @@ SUBROUTINE put_hycom(file_in_a,file_in_b,v3d,v2d,mskp,msku,mskv)
read(110,'(a)') cline
i= index(cline,'=')
read (cline(i+1:),*) nstep,time(1),layer,thbase,hminb,hmaxb
where (abs(dummy_2d-hycom_undef) > hycom_eps) mskv=1

CALL ZAIOWR(dummy_2d,mskv,.true.,xmin,xmax,24,.false.)
write(24,117) 'vmix ',nstep,time(1),layer,thbase,xmin,xmax
Expand Down

0 comments on commit a0217bd

Please sign in to comment.