Skip to content

Commit

Permalink
Updated NACC for Fengsha (needs UTHRES)
Browse files Browse the repository at this point in the history
  • Loading branch information
Patrick.C.Campbell@noaa.gov authored and Patrick.C.Campbell@noaa.gov committed Jun 29, 2020
1 parent 9b1dd02 commit ef2f28b
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 32 deletions.
32 changes: 16 additions & 16 deletions parallel/src/rdfv3.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1459,12 +1459,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'CLAY_FRAC', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
clayf(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! CLAYF check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 water = 0 or frac > 1, set CLAYF < 0.0
clayf = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 water = 0 or frac > 1, set CLAYF < 0.0
! clayf = -1.0
! END WHERE
WRITE (*,ifmt2) 'CLAYF ', clayf(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'CLAYF', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1503,12 +1503,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'SAND_FRAC', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
sandf(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! SANDF check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) .OR. (sandf > 1.0) ) ! FV3 water = 0 or frac > 1, set SANDF < 0.0
sandf = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) .OR. (sandf > 1.0) ) ! FV3 water = 0 or frac > 1, set SANDF < 0.0
! sandf = -1.0
! END WHERE
WRITE (*,ifmt2) 'SANDF ', sandf(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'SANDF', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1547,12 +1547,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'DRAG_PART', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
drag(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! DRAG check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and DRAG < 0.0
drag = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and DRAG < 0.0
! drag = -1.0
! END WHERE
WRITE (*,ifmt2) 'DRAG ', drag(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'DRAG', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1591,12 +1591,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'SSM', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
ssm(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! SSM check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and CLAYF < 0.0
ssm = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and CLAYF < 0.0
! ssm = -1.0
! END WHERE
WRITE (*,ifmt2) 'SSM ', ssm(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'SSM', TRIM(nf90_strerror(rcode))
Expand Down
32 changes: 16 additions & 16 deletions serial/src/rdfv3.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1448,12 +1448,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'CLAY_FRAC', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
clayf(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! CLAYF check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 water = 0 and CLAYF < 0.0
clayf = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 water = 0 and CLAYF < 0.0
! clayf = -1.0
! END WHERE
WRITE (*,ifmt2) 'CLAYF ', clayf(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'CLAYF', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1492,12 +1492,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'SAND_FRAC', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
sandf(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! SANDF check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 land = 1 and SANDF < 0.0
sandf = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) .OR. (clayf > 1.0) ) ! FV3 land = 1 and SANDF < 0.0
! sandf = -1.0
! END WHERE
WRITE (*,ifmt2) 'SANDF ', sandf(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'SANDF', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1536,12 +1536,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'DRAG_PART', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
drag(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! DRAG check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and DRAG < 0.0
drag = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and DRAG < 0.0
! drag = -1.0
! END WHERE
WRITE (*,ifmt2) 'DRAG ', drag(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'DRAG', TRIM(nf90_strerror(rcode))
Expand Down Expand Up @@ -1580,12 +1580,12 @@ END SUBROUTINE windrotation
ENDIF
CALL get_var_2d_real_cdf (cdfidg, 'SSM', dum2d, 1, rcode)
IF ( rcode == nf90_noerr ) THEN
call myinterp(dum2d(1:met_nx, met_ny:1:-1),met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
call myinterp(dum2d,met_nx,met_ny,atmp,xindex,yindex,ncols_x,nrows_x,1)
ssm(1:ncols_x,1:nrows_x) = atmp(1:ncols_x,1:nrows_x)
! SSM check over water, set as negative numbers for improved error checking
WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and CLAYF < 0.0
ssm = -1.0
END WHERE
! WHERE ( (INT(landmask) == 0) ) ! FV3 water = 0 and CLAYF < 0.0
! ssm = -1.0
! END WHERE
WRITE (*,ifmt2) 'SSM ', ssm(lprt_metx,lprt_mety)
ELSE
WRITE (*,f9400) TRIM(pname), 'SSM', TRIM(nf90_strerror(rcode))
Expand Down

0 comments on commit ef2f28b

Please sign in to comment.