7 S, P, PEK, IO, HPROGRAM)
54 USE modi_init_io_surf_n
56 USE modi_end_io_surf_n
69 CHARACTER(LEN=*),
DIMENSION(:),
INTENT(IN) :: HSELECT
71 LOGICAL,
INTENT(IN) :: OSURF_DIAG_ALBEDO
77 CHARACTER(LEN=6),
INTENT(IN) :: HPROGRAM
83 CHARACTER(LEN=12) :: YRECFM
84 CHARACTER(LEN=100):: YCOMMENT
85 CHARACTER(LEN=2) :: YLVLV, YPAS
88 REAL(KIND=JPRB) :: ZHOOK_HANDLE
93 IF (
lhook)
CALL dr_hook(
'WRITE_DIAG_PGD_GRDN_N',0,zhook_handle)
94 CALL init_io_surf_n(dtco, u, hprogram,
'TOWN ',
'TEB ',
'WRITE',
'TEB_PGD.OUT.nc' 98 IF (io%CPHOTO==
'NON' .OR. io%CPHOTO==
'AST')
THEN 101 ycomment=
'leaf area index (-)' 103 CALL write_surf(hselect,hprogram,yrecfm,pek%XLAI(:),iresp,hcomment=ycomment
112 ycomment=
'vegetation fraction (-)' 114 CALL write_surf(hselect,hprogram,yrecfm,pek%XVEG(:),iresp,hcomment=ycomment
119 ycomment=
'surface roughness length (without snow) (M)' 121 CALL write_surf(hselect,hprogram,yrecfm,pek%XZ0(:),iresp,hcomment=ycomment
127 DO jl=1,
SIZE(p%XDG,2)
128 WRITE(yrecfm,fmt=
'(A5,I1)')
'GD_DG',jl
129 ycomment=
'soil depth'//
' (M)' 130 CALL write_surf(hselect,hprogram,yrecfm,p%XDG(:,jl),iresp,hcomment=ycomment
137 IF (
lhook)
CALL dr_hook(
'WRITE_DIAG_PGD_GRDN_N',1,zhook_handle)
145 IF(io%CHORT==
'SGH')
THEN 147 ycomment=
'soil ice depth for runoff (m)' 148 CALL write_surf(hselect,hprogram,yrecfm,p%XD_ICE(:),iresp,hcomment=ycomment
155 DO jl=1,
SIZE(s%XVEGTYPE,2)
156 WRITE(ypas,
'(I2)') jl
157 ylvlv=adjustl(ypas(:len_trim(ypas)))
158 WRITE(yrecfm,fmt=
'(A12)')
'GD_VEGTY_P'//ylvlv
159 ycomment=
'fraction of each vegetation type '//
' (-)' 160 CALL write_surf(hselect,hprogram,yrecfm,s%XVEGTYPE(:,jl),iresp,hcomment
167 ycomment=
'minimum stomatal resistance (SM-1)' 168 CALL write_surf(hselect,hprogram,yrecfm,pek%XRSMIN(:),iresp,hcomment=ycomment
171 ycomment=
'coefficient for RSMIN calculation (-)' 172 CALL write_surf(hselect,hprogram,yrecfm,pek%XGAMMA(:),iresp,hcomment=ycomment
175 ycomment=
'vegetation thermal inertia coefficient (-)' 176 CALL write_surf(hselect,hprogram,yrecfm,pek%XCV(:),iresp,hcomment=ycomment
179 ycomment=
'maximum solar radiation usable in photosynthesis (-)' 180 CALL write_surf(hselect,hprogram,yrecfm,pek%XRGL(:),iresp,hcomment=ycomment
182 yrecfm=
'GD_EMIS_ISBA' 183 ycomment=
'surface emissivity (-)' 184 CALL write_surf(hselect,hprogram,yrecfm,pek%XEMIS(:),iresp,hcomment=ycomment
187 ycomment=
'coefficient for maximum water interception (-)' 188 CALL write_surf(hselect,hprogram,yrecfm,pek%XWRMAX_CF(:),iresp,hcomment
192 IF (osurf_diag_albedo)
THEN 198 ycomment=
'soil near-infra-red albedo (-)' 199 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBNIR_SOIL(:),iresp,hcomment
204 ycomment=
'soil visible albedo (-)' 205 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBVIS_SOIL(:),iresp,hcomment
210 ycomment=
'soil UV albedo (-)' 211 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBUV_SOIL(:),iresp,hcomment
218 ycomment=
'total near-infra-red albedo (-)' 219 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBNIR(:),iresp,hcomment
224 ycomment=
'total visible albedo (-)' 225 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBVIS(:),iresp,hcomment
230 ycomment=
'total UV albedo (-)' 231 CALL write_surf(hselect,hprogram,yrecfm,pek%XALBUV(:),iresp,hcomment=ycomment
240 IF (
lhook)
CALL dr_hook(
'WRITE_DIAG_PGD_GRDN_N',1,zhook_handle)
subroutine end_io_surf_n(HPROGRAM)
subroutine write_diag_pgd_grdn_n(DTCO, HSELECT, U, OSURF_DIAG_ALB
logical, save lfanocompact
subroutine init_io_surf_n(DTCO, U, HPROGRAM, HMASK, HSCHEME, HACTION