Skip to content

Commit

Permalink
Merge pull request #845 from GEOS-ESM/feature/borescan_cleanup_coeffsib
Browse files Browse the repository at this point in the history
minor land related code cleanup (coeffsib)
  • Loading branch information
sdrabenh committed Nov 9, 2023
2 parents f977edd + 25944ed commit 32f555f
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 14 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -102,8 +102,6 @@ MODULE CATCHMENT_CN_MODEL
catch_calc_wtotl, dampen_tc_oscillations, &
SRUNOFF

USE SIBALB_COEFF, ONLY: coeffsib

USE STIEGLITZSNOW, ONLY: &
StieglitzSnow_snowrt, &
StieglitzSnow_calc_asnow, &
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -103,8 +103,6 @@ MODULE CATCHMENT_MODEL
catch_calc_wtotl, dampen_tc_oscillations, &
SRUNOFF

USE SIBALB_COEFF, ONLY: coeffsib

USE STIEGLITZSNOW, ONLY: &
StieglitzSnow_snowrt, &
StieglitzSnow_calc_asnow, &
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1655,8 +1655,6 @@ SUBROUTINE SIBALB (NCH, ITYP, VLAI, VGRN, ZTH, &
MODIS_SCALE_ = .FALSE.
END IF

!FPP$ EXPAND (COEFFSIB)

DO I=1,NCH

ALA = AMIN1 (AMAX1 (ZERO, VLAI(I)), ALATRM)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1540,14 +1540,16 @@ SUBROUTINE StieglitzSnow_trid(X,DD,D,RD,B,N)
integer I,J
real*4 RSF
RSF=0.
DO 10 I=2,N
do I=2,N
J=N+1-I
if(D(J+1).ne.0.) RSF=RD(J)/D(J+1)
D(J)=D(J)-DD(J+1)*RSF
10 B(J)=B(J)- B(J+1)*RSF
B(J)=B(J)- B(J+1)*RSF
enddo
if(D(1).ne.0.) X(1)=B(1)/D(1)
DO 20 J=2,N
20 if(D(J).ne.0.) X(J)=(B(J)-DD(J)*X(J-1))/D(J)
do J=2,N
if(D(J).ne.0.) X(J)=(B(J)-DD(J)*X(J-1))/D(J)
enddo
RETURN

END SUBROUTINE StieglitzSnow_trid
Expand Down Expand Up @@ -1641,8 +1643,6 @@ SUBROUTINE StieglitzSnow_snow_albedo( &

! *********************************************************************

!FPP$ EXPAND (COEFFSIB)

if(SLOPE < 0.0) then
GK_B = SLOPE
else
Expand Down Expand Up @@ -1775,8 +1775,6 @@ SUBROUTINE ALB_WITH_IMPURITY (N_snow, ZTH, &

! *********************************************************************

!FPP$ EXPAND (COEFFSIB)

SZTH=ZTH
DEGSZA=ACOS(SZTH)*180./PIE
SZASIN=SQRT(1.-(SZTH**2.0))
Expand Down

0 comments on commit 32f555f

Please sign in to comment.