Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
Expand Up @@ -146,11 +146,10 @@ module catch_constants
! NLv5 | PEATMAP | poros=0.93
!
! - reichle, 26 Jan 2022

REAL, PARAMETER, PUBLIC :: PEATCLSM_POROS_THRESHOLD = 0.90 ! [m3/m3]
! max zbar for specific yield calc in PEATCLSM

! max zbar for specific yield calc in PEATCLSM

REAL, PARAMETER, PUBLIC :: PEATCLSM_ZBARMAX_4_SYSOIL = 0.45 ! [m]

contains
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -546,7 +546,7 @@ SUBROUTINE RZDRAIN ( &

SRFLW=SRFEXC(N)*DTSTEP/TSC0

IF(SRFLW < 0. ) SRFLW = FLWALPHA * SRFLW ! C05 change
IF ((POROS(N) .LT. 0.67) .AND. (SRFLW < 0. )) SRFLW = FLWALPHA * SRFLW ! C05 change

!rr following inserted by koster Sep 22, 2003
rzdif=rzave/poros(n)-wpwet(n)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,6 @@ program Scale_Catch
real, pointer :: ghtcnt4(:)
real, pointer :: ghtcnt5(:)
real, pointer :: ghtcnt6(:)
real, pointer :: tsurf(:)
real, pointer :: wesnn1(:)
real, pointer :: wesnn2(:)
real, pointer :: wesnn3(:)
Expand All @@ -83,11 +82,6 @@ program Scale_Catch
real, pointer :: sndzn1(:)
real, pointer :: sndzn2(:)
real, pointer :: sndzn3(:)
real, pointer :: ch(:,:)
real, pointer :: cm(:,:)
real, pointer :: cq(:,:)
real, pointer :: fr(:,:)
real, pointer :: ww(:,:)
endtype catch_rst

type(catch_rst) catch(3)
Expand Down Expand Up @@ -441,7 +435,6 @@ subroutine allocatch (ntiles,catch)
allocate( catch% ghtcnt4(ntiles) )
allocate( catch% ghtcnt5(ntiles) )
allocate( catch% ghtcnt6(ntiles) )
allocate( catch% tsurf(ntiles) )
allocate( catch% wesnn1(ntiles) )
allocate( catch% wesnn2(ntiles) )
allocate( catch% wesnn3(ntiles) )
Expand All @@ -451,11 +444,6 @@ subroutine allocatch (ntiles,catch)
allocate( catch% sndzn1(ntiles) )
allocate( catch% sndzn2(ntiles) )
allocate( catch% sndzn3(ntiles) )
allocate( catch% ch(ntiles,4) )
allocate( catch% cm(ntiles,4) )
allocate( catch% cq(ntiles,4) )
allocate( catch% fr(ntiles,4) )
allocate( catch% ww(ntiles,4) )

return
end subroutine allocatch
Expand Down Expand Up @@ -510,7 +498,6 @@ subroutine readcatch_nc4 (catch,formatter, rc)
call MAPL_VarRead(formatter,"GHTCNT4",catch%ghtcnt4, __RC__)
call MAPL_VarRead(formatter,"GHTCNT5",catch%ghtcnt5, __RC__)
call MAPL_VarRead(formatter,"GHTCNT6",catch%ghtcnt6, __RC__)
call MAPL_VarRead(formatter,"TSURF",catch%tsurf, __RC__)
call MAPL_VarRead(formatter,"WESNN1",catch%wesnn1, __RC__)
call MAPL_VarRead(formatter,"WESNN2",catch%wesnn2, __RC__)
call MAPL_VarRead(formatter,"WESNN3",catch%wesnn3, __RC__)
Expand All @@ -520,11 +507,6 @@ subroutine readcatch_nc4 (catch,formatter, rc)
call MAPL_VarRead(formatter,"SNDZN1",catch%sndzn1, __RC__)
call MAPL_VarRead(formatter,"SNDZN2",catch%sndzn2, __RC__)
call MAPL_VarRead(formatter,"SNDZN3",catch%sndzn3, __RC__)
call MAPL_VarRead(formatter,"CH",catch%ch, __RC__)
call MAPL_VarRead(formatter,"CM",catch%cm, __RC__)
call MAPL_VarRead(formatter,"CQ",catch%cq, __RC__)
call MAPL_VarRead(formatter,"FR",catch%fr, __RC__)
call MAPL_VarRead(formatter,"WW",catch%ww, __RC__)
if (present(rc)) rc =0
!_RETURN(_SUCCESS)
end subroutine readcatch_nc4
Expand Down Expand Up @@ -575,7 +557,6 @@ subroutine readcatch (unit,catch)
read(unit) catch% ghtcnt4
read(unit) catch% ghtcnt5
read(unit) catch% ghtcnt6
read(unit) catch% tsurf
read(unit) catch% wesnn1
read(unit) catch% wesnn2
read(unit) catch% wesnn3
Expand All @@ -585,11 +566,6 @@ subroutine readcatch (unit,catch)
read(unit) catch% sndzn1
read(unit) catch% sndzn2
read(unit) catch% sndzn3
read(unit) catch% ch
read(unit) catch% cm
read(unit) catch% cq
read(unit) catch% fr
read(unit) catch% ww

return
end subroutine readcatch
Expand Down Expand Up @@ -641,7 +617,6 @@ subroutine writecatch_nc4 (catch,formatter)
call MAPL_VarWrite(formatter,"GHTCNT4",catch%ghtcnt4)
call MAPL_VarWrite(formatter,"GHTCNT5",catch%ghtcnt5)
call MAPL_VarWrite(formatter,"GHTCNT6",catch%ghtcnt6)
call MAPL_VarWrite(formatter,"TSURF",catch%tsurf)
call MAPL_VarWrite(formatter,"WESNN1",catch%wesnn1)
call MAPL_VarWrite(formatter,"WESNN2",catch%wesnn2)
call MAPL_VarWrite(formatter,"WESNN3",catch%wesnn3)
Expand All @@ -651,11 +626,6 @@ subroutine writecatch_nc4 (catch,formatter)
call MAPL_VarWrite(formatter,"SNDZN1",catch%sndzn1)
call MAPL_VarWrite(formatter,"SNDZN2",catch%sndzn2)
call MAPL_VarWrite(formatter,"SNDZN3",catch%sndzn3)
call MAPL_VarWrite(formatter,"CH",catch%ch)
call MAPL_VarWrite(formatter,"CM",catch%cm)
call MAPL_VarWrite(formatter,"CQ",catch%cq)
call MAPL_VarWrite(formatter,"FR",catch%fr)
call MAPL_VarWrite(formatter,"WW",catch%ww)

return
end subroutine writecatch_nc4
Expand Down Expand Up @@ -706,7 +676,6 @@ subroutine writecatch (unit,catch)
write(unit) catch% ghtcnt4
write(unit) catch% ghtcnt5
write(unit) catch% ghtcnt6
write(unit) catch% tsurf
write(unit) catch% wesnn1
write(unit) catch% wesnn2
write(unit) catch% wesnn3
Expand All @@ -716,11 +685,6 @@ subroutine writecatch (unit,catch)
write(unit) catch% sndzn1
write(unit) catch% sndzn2
write(unit) catch% sndzn3
write(unit) catch% ch
write(unit) catch% cm
write(unit) catch% cq
write(unit) catch% fr
write(unit) catch% ww

return
end subroutine writecatch
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -72,10 +72,10 @@ PROGRAM mk_GEOSldasRestarts
integer, parameter :: ntiles_cn = 1684725, ntiles_cat = 1653157
character(len=300), parameter :: &
InCNRestart = '/discover/nobackup/projects/gmao/ssd/land/l_data/LandRestarts_for_Regridding/CatchCN/M09/20151231/catchcn_internal_rst', &
InCNTilFile = '/discover/nobackup/ltakacs/bcs/Heracles-NL/SMAP_EASEv2_M09/SMAP_EASEv2_M09_3856x1624.til', &
InCatRestart= '/discover/nobackup/projects/gmao/ssd/land/l_data/LandRestarts_for_Regridding/Catch/M09/20170101/catch_internal_rst', &
InCatTilFile= '/discover/nobackup/projects/gmao/ssd/land/l_data/geos5/bcs/CLSM_params/mkCatchParam_SMAP_L4SM_v002/' &
//'SMAP_EASEv2_M09/SMAP_EASEv2_M09_3856x1624.til', &
InCNTilFile = '/dodrio/scratch/projects/2022_200/project_output/rsda/vsc32460/CLSM_params/NL5/SMAP_EASEv2_M09/SMAP_EASEv2_M09_3856x1624.til', &
InCatRestart= '/data/leuven/324/vsc32460/projects/GEOSldas/SMAP_Nature_v8.3/output/SMAP_EASEv2_M09_GLOBAL/rs/ens0000/' &
//'Y2000/M01/SMAP_Nature_v8.3.catch_internal_rst.20000101_0000', &
InCatTilFile= '/dodrio/scratch/projects/2022_200/project_output/rsda/vsc32460/CLSM_params/NL5/SMAP_EASEv2_M09/SMAP_EASEv2_M09_3856x1624.til', &
InCatRest45 = '/discover/nobackup/projects/gmao/ssd/land/l_data/LandRestarts_for_Regridding/Catch/M09/20170101/catch_internal_rst', &
InCatTil45 = '/discover/nobackup/projects/gmao/ssd/land/l_data/geos5/bcs/CLSM_params/mkCatchParam_SMAP_L4SM_v002/' &
//'SMAP_EASEv2_M09/SMAP_EASEv2_M09_3856x1624.til'
Expand Down Expand Up @@ -540,8 +540,10 @@ SUBROUTINE regrid_from_xgrid (SURFLAY, BCSDIR, YYYYMMDDHH, EXPNAME, EXPDIR, MOD

filetype = 0
call MAPL_NCIOGetFileType(rst_file, filetype,__RC__)
print *, 'SA: filetype is (should be 0): ', filetype
if(filetype == 0) then
! GEOSldas CATCH/CATCHCN or CATCHCN LDASsa
print*, 'SA: rst_file is:', rst_file
call put_land_vars (NTILES, ntiles_rst, id_glb, ld_reorder, model, rst_file)
else
call read_ldas_restarts (NTILES, ntiles_rst, id_glb, ld_reorder, rst_file, pfile)
Expand Down Expand Up @@ -1357,6 +1359,7 @@ SUBROUTINE read_bcs_data (ntiles, SURFLAY,MODEL, DataDir, InRestart, rc)
inquire(file = trim(DataDir)//"CLM_veg_typs_fracs" ,exist=NewLand )

isCatchCN = (index(model,'catchcn') /=0)
print *, 'SA! check if isCatchCN is False or 0:', isCatchCN

if(file_exists) then

Expand Down Expand Up @@ -1451,6 +1454,7 @@ SUBROUTINE read_bcs_data (ntiles, SURFLAY,MODEL, DataDir, InRestart, rc)
! W.J notes: CanopH is not used. If CLM_veg_typs_fracs exists, the read some dummy ???? Ask Sarith
if (NewLand) then
read(21,*) I, j, ITY(N),idum, rdum, rdum, CanopH(N)
print *, 'SA!: NewLand is True and ITY value is (should correspond to mosaic_veg_typs_fracs):', ITY(N)
else
read(21,*) I, j, ITY(N),idum, rdum, rdum
endif
Expand Down Expand Up @@ -1689,6 +1693,8 @@ SUBROUTINE read_bcs_data (ntiles, SURFLAY,MODEL, DataDir, InRestart, rc)
! -----------------------------------------------------------------------

STATUS = NF_OPEN (trim(InRestart),NF_WRITE,NCFID) ; VERIFY_(STATUS)
print *, 'SA! The InRestart netcdf is opened and variables are written to it, this is the InRestart file:', InRestart
print *, 'SA! Print of the STATUS after opening (1):', STATUS
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'BF1'), (/1/), (/NTILES/),BF1)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'BF2'), (/1/), (/NTILES/),BF2)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'BF3'), (/1/), (/NTILES/),BF3)
Expand Down Expand Up @@ -1718,10 +1724,11 @@ SUBROUTINE read_bcs_data (ntiles, SURFLAY,MODEL, DataDir, InRestart, rc)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'TSB2'), (/1/), (/NTILES/),TSB2)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'ATAU'), (/1/), (/NTILES/),ATAU2)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'BTAU'), (/1/), (/NTILES/),BTAU2)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'TILE_ID'), (/1/), (/NTILES/),VAR1)
! STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'TILE_ID'), (/1/), (/NTILES/),VAR1)
print *, 'SA! Print of the STATUS after reading in all regular variables and outcommenting TILE ID (2):', STATUS
! STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'OLD_ITY'), (/1/), (/NTILES/),real(ITY))

if( isCatchCN ) then

STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'ITY'), (/1,1/), (/NTILES,1/),CLMC_pt1)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'ITY'), (/1,2/), (/NTILES,1/),CLMC_pt2)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'ITY'), (/1,3/), (/NTILES,1/),CLMC_st1)
Expand Down Expand Up @@ -1750,11 +1757,17 @@ SUBROUTINE read_bcs_data (ntiles, SURFLAY,MODEL, DataDir, InRestart, rc)
endif

else
print *, 'SA! If this is written the ITY is assigned to the OLD_ITY in the netcdf'
print *, 'SA! This is the ITY assigned to the OLD_ITY in the netcdf file, check if value 12 is 4 (correct) or 5 (incorrect)', ITY(1:NTILES)
STATUS = NF_PUT_VARA_REAL(NCFID,VarID(NCFID,'OLD_ITY'), (/1/), (/NTILES/),real(ITY))
endif
print *, 'SA! Print of the STATUS after the if else block (3):', STATUS

STATUS = NF_CLOSE ( NCFID)

print *, 'SA! Print of the STATUS after closing the netcdf (4):', STATUS


deallocate ( BF1, BF2, BF3 )
deallocate (VGWMAX, CDCR1, CDCR2 )
deallocate ( PSIS, BEE, POROS )
Expand Down Expand Up @@ -2559,25 +2572,27 @@ SUBROUTINE put_land_vars (NTILES, ntiles_rst, id_glb, ld_reorder, model, rst_fil
endif
endif
if(trim(model) == 'catch' ) then
call InFmt%open(trim(InCatRestart), pFIO_READ, __RC__)
print *, 'SA: Restart path for rewriting: ', InCatRestart
call InFmt%open(trim(InCatRestart), pFIO_READ, __RC__)
endif
meta_data = InFmt%read(__RC__)
call InFmt%close(__RC__)

call meta_data%modify_dimension('tile', ntiles, __RC__)

OutFileName = "InData/"//trim(model)//"_internal_rst"

call OutFmt%create(trim(OutFileName),__RC__)
call OutFmt%write(meta_data,__RC__)

if (present(rst_file)) then
print*, 'rst_file is present:', rst_file
STATUS = NF_OPEN (trim(rst_file ),NF_NOWRITE,NCFID) ; VERIFY_(STATUS)
else
if(index(model, 'catchcn') /=0 ) then
STATUS = NF_OPEN (trim(InCNRestart ),NF_NOWRITE,NCFID) ; VERIFY_(STATUS)
endif
if(trim(model) == 'catch') then
print*, 'rst_file is not present and InCatRestart is used:', InCatRestart
STATUS = NF_OPEN (trim(InCatRestart),NF_NOWRITE,NCFID) ; VERIFY_(STATUS)
endif
endif
Expand All @@ -2591,6 +2606,12 @@ SUBROUTINE put_land_vars (NTILES, ntiles_rst, id_glb, ld_reorder, model, rst_fil
end do
call MAPL_VarWrite(OutFmt,'POROS',var_put)

STATUS = NF_GET_VARA_REAL(NCFID,VarID(NCFID,'OLD_ITY' ), (/1/), (/NTILES_RST/),var_get)
do k = 1, NTILES
VAR_PUT(k) = var_get(ld_reorder(id_glb(k)))
end do
call MAPL_VarWrite(OutFmt,'OLD_ITY',var_put)

STATUS = NF_GET_VARA_REAL(NCFID,VarID(NCFID,'COND' ), (/1/), (/NTILES_RST/),var_get)
do k = 1, NTILES
VAR_PUT(k) = var_get(ld_reorder(id_glb(k)))
Expand Down