SURFEX v8.1
General documentation of Surfex
writesurf_teb_greenroofn.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE writesurf_teb_greenroof_n (HSELECT, OSNOWDIMNC, IO, S, PEK, HPROGRAM,HPATCH)
7 ! #####################################
8 !
9 !!**** *WRITESURF_TEB_GREENROOF_n* - writes ISBA prognostic fields
10 !!
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! Based on "writesurf_teb_gardenn"
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! A. Lemonsu & C. de Munck
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 07/2011
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
44 USE modd_isba_n, ONLY : isba_pe_t, isba_s_t
45 !
47 USE modi_writesurf_gr_snow
48 USE modd_dst_surf
49 !
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
61 LOGICAL, INTENT(IN) :: OSNOWDIMNC
62 !
63 TYPE(isba_options_t), INTENT(IN) :: IO
64 TYPE(isba_s_t), INTENT(INOUT) :: S
65 TYPE(isba_pe_t), INTENT(IN) :: PEK
66 !
67  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
68  CHARACTER(LEN=3), INTENT(IN) :: HPATCH ! current teb patch
69 !
70 !* 0.2 Declarations of local variables
71 ! -------------------------------
72 !
73 INTEGER, DIMENSION(SIZE(PEK%XTG,1)) :: IMASK_P
74 INTEGER :: IRESP ! IRESP : return-code if a problem appears
75  CHARACTER(LEN=30) :: YRECFM ! Name of the article to be read
76  CHARACTER(LEN=100) :: YCOMMENT ! Comment string
77  CHARACTER(LEN=14) :: YFORM ! Writing format
78  CHARACTER(LEN=4 ) :: YLVL
79 !
80 INTEGER :: JL, JI ! loop counter on soil layers
81 !
82 REAL, DIMENSION(:), ALLOCATABLE :: ZWORK ! 2D array to write data in file
83 !
84 INTEGER :: IWORK ! Work integer
85 !
86 INTEGER :: JSV, JNBIOMASS
87 !
88 REAL(KIND=JPRB) :: ZHOOK_HANDLE
89 !
90 !------------------------------------------------------------------------------
91 !
92 !* 2. Prognostic fields:
93 ! -----------------
94 !
95 IF (lhook) CALL dr_hook('WRITESURF_TEB_GREENROOF_N',0,zhook_handle)
96 ALLOCATE(zwork(SIZE(pek%XTG,1)))
97 !
98 !
99 !* soil temperatures
100 !
101 iwork=io%NGROUND_LAYER
102 !
103 DO jl=1,iwork
104  WRITE(ylvl,'(I2)') jl
105  yrecfm=hpatch//'GR_TG'//adjustl(ylvl(:len_trim(ylvl)))
106  yrecfm=adjustl(yrecfm)
107  yform='(A13,I1.1,A4)'
108  IF (jl >= 10) yform='(A13,I2.2,A4)'
109  WRITE(ycomment,fmt=yform) 'X_Y_TWN_TG_GR',jl,' (K)'
110  zwork=pek%XTG(:,jl)
111  CALL write_surf(hselect, hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
112 END DO
113 !
114 !* soil liquid water content
115 !
116 DO jl=1,io%NGROUND_LAYER
117  WRITE(ylvl,'(I2)') jl
118  yrecfm=hpatch//'GR_WG'//adjustl(ylvl(:len_trim(ylvl)))
119  yrecfm=adjustl(yrecfm)
120  yform='(A13,I1.1,A8)'
121  IF (jl >= 10) yform='(A13,I2.2,A8)'
122  WRITE(ycomment,fmt=yform) 'X_Y_TWN_WG_GR',jl,' (m3/m3)'
123  zwork=pek%XWG(:,jl)
124  CALL write_surf(hselect, hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
125 END DO
126 !
127 !
128 !* soil ice water content
129 !
130 DO jl=1,io%NGROUND_LAYER
131  WRITE(ylvl,'(I2)') jl
132  yrecfm=hpatch//'GR_WGI'//adjustl(ylvl(:len_trim(ylvl)))
133  yrecfm=adjustl(yrecfm)
134  yform='(A14,I1.1,A8)'
135  IF (jl >= 10) yform='(A14,I2.2,A8)'
136  WRITE(ycomment,yform) 'X_Y_GR_WGI',jl,' (m3/m3)'
137  zwork=pek%XWGI(:,jl)
138  CALL write_surf(hselect, hprogram,yrecfm,zwork,iresp,hcomment=ycomment)
139 END DO
140 !
141 DEALLOCATE(zwork)
142 !
143 !* water intercepted on leaves
144 !
145 yrecfm=hpatch//'GR_WR'
146 yrecfm=adjustl(yrecfm)
147 ycomment='X_Y_TWN_WR_GR (kg/m2)'
148  CALL write_surf(hselect, hprogram,yrecfm,pek%XWR(:),iresp,hcomment=ycomment)
149 !
150 !* Leaf Area Index
151 !
152 IF (io%CPHOTO/='NON' .AND. io%CPHOTO/='AST') THEN
153  yrecfm=hpatch//'GR_LAI'
154  yrecfm=adjustl(yrecfm)
155  ycomment='X_Y_GR_LAI (m2/m2)'
156  CALL write_surf(hselect, hprogram,yrecfm,pek%XLAI(:),iresp,hcomment=ycomment)
157 END IF
158 !
159 !
160 !* biomass
161 !
162 IF (io%CPHOTO=='NIT') THEN
163  DO jnbiomass=1,io%NNBIOMASS
164  WRITE(ylvl,'(I1)') jnbiomass
165  yrecfm=hpatch//'GR_BIOMA'//adjustl(ylvl(:len_trim(ylvl)))
166  yrecfm=adjustl(yrecfm)
167  yform='(A11,I1.1,A8)'
168  WRITE(ycomment,fmt=yform) 'X_Y_BIOMASS',jnbiomass,' (kg/m2)'
169  CALL write_surf(hselect, hprogram,yrecfm,pek%XBIOMASS(:,jnbiomass),iresp,hcomment=ycomment)
170  END DO
171  !
172  !
173  DO jnbiomass=2,io%NNBIOMASS
174  WRITE(ylvl,'(I1)') jnbiomass
175  yrecfm=hpatch//'GR_RESPI'//adjustl(ylvl(:len_trim(ylvl)))
176  yrecfm=adjustl(yrecfm)
177  yform='(A16,I1.1,A10)'
178  WRITE(ycomment,fmt=yform) 'X_Y_RESP_BIOMASS',jnbiomass,' (kg/m2/s)'
179  CALL write_surf(hselect, hprogram,yrecfm,pek%XRESP_BIOMASS(:,jnbiomass),iresp,hcomment=ycomment)
180  END DO
181 END IF
182 !
183 !* aerodynamical resistance
184 !
185 !
186 yrecfm=hpatch//'GR_RESA'
187 yrecfm=adjustl(yrecfm)
188 ycomment='X_Y_GR_RESA (s/m)'
189  CALL write_surf(hselect, hprogram,yrecfm,pek%XRESA(:),iresp,hcomment=ycomment)
190 !
191 !* snow mantel
192 !
193 DO ji = 1,SIZE(imask_p)
194  imask_p(ji) = ji
195 ENDDO
196 yrecfm='GR'
197  CALL writesurf_gr_snow(osnowdimnc, hselect, hprogram, yrecfm, hpatch, &
198  SIZE(pek%XTG,1), imask_p, 0, pek%TSNOW, s%XWSN_WR, &
199  s%XRHO_WR, s%XHEA_WR, s%XAGE_WR, s%XSG1_WR, s%XSG2_WR, &
200  s%XHIS_WR, s%XALB_WR)
201 
202 !
203 IF (lhook) CALL dr_hook('WRITESURF_TEB_GREENROOF_N',1,zhook_handle)
204 !
205 !-------------------------------------------------------------------------------
206 !
207 END SUBROUTINE writesurf_teb_greenroof_n
integer, parameter jprb
Definition: parkind1.F90:32
subroutine writesurf_teb_greenroof_n(HSELECT, OSNOWDIMNC, IO, S,
logical lhook
Definition: yomhook.F90:15
subroutine writesurf_gr_snow(OSNOWDIMNC, HSELECT, HPROGRAM, HSURF