SURFEX v8.1
General documentation of Surfex
read_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 read_teb_greenroof_n (DTCO, U, IO, P, PEK, HPROGRAM,HPATCH)
7 ! ##################################
8 !
9 !!**** *READ_TEB_GREENROOF_n* - routine to initialise ISBA variables
10 !!
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !! based on read_teb_greenroofn
28 !!
29 !! AUTHOR
30 !! ------
31 !! C. de Munck & A. Lemonsu *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 07/2011
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 !
43 !
44 !
46 USE modd_surf_atm_n, ONLY : surf_atm_t
47 !
49 USE modd_isba_n, ONLY : isba_pe_t, isba_p_t
50 !
51 USE modd_co2v_par, ONLY : xanfminit, xcondctmin
52 !
53 USE modd_surf_par, ONLY : xundef
54 USE modd_snow_par, ONLY : xz0sn
55 !
57 !
58 USE modi_read_gr_snow
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_get_type_dim_n
64 !
65 IMPLICIT NONE
66 !
67 !* 0.1 Declarations of arguments
68 ! -------------------------
69 !
70 !
71 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
72 TYPE(surf_atm_t), INTENT(INOUT) :: U
73 !
74 TYPE(isba_options_t), INTENT(INOUT) :: IO
75 TYPE(isba_p_t), INTENT(INOUT) :: P
76 TYPE(isba_pe_t), INTENT(INOUT) :: PEK
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
79  CHARACTER(LEN=3), INTENT(IN) :: HPATCH ! current TEB patch identificator
80 !
81 !* 0.2 Declarations of local variables
82 ! -------------------------------
83 INTEGER :: ILU ! 1D physical dimension
84 INTEGER :: IRESP ! Error code after redding
85 INTEGER :: IWORK ! Work integer
86 INTEGER :: JLAYER, JNBIOMASS ! loop counter on layers
87  CHARACTER(LEN=30) :: YRECFM ! Name of the article to be read
88  CHARACTER(LEN=4) :: YLVL
89 REAL, DIMENSION(:),ALLOCATABLE :: ZWORK ! 2D array to write data in file
90 !
91 REAL(KIND=JPRB) :: ZHOOK_HANDLE
92 !
93 !-------------------------------------------------------------------------------
94 !
95 !
96 !* 1D physical dimension
97 !
98 IF (lhook) CALL dr_hook('READ_TEB_GREENROOF_N',0,zhook_handle)
99 yrecfm='SIZE_TOWN'
100  CALL get_type_dim_n(dtco, u, 'TOWN ',ilu)
101 !
102 !
103 !* 2. Prognostic fields:
104 ! -----------------
105 !
106 ALLOCATE(zwork(ilu))
107 !
108 !* soil temperatures
109 !
110 iwork = io%NGROUND_LAYER
111 !
112 DO jlayer=1,iwork
113  WRITE(ylvl,'(I2)') jlayer
114  yrecfm=hpatch//'GR_TG'//adjustl(ylvl(:len_trim(ylvl)))
115  yrecfm=adjustl(yrecfm)
116  CALL read_surf(hprogram,yrecfm,zwork(:),iresp)
117  pek%XTG(:,jlayer) = zwork
118 END DO
119 !
120 !
121 !* soil liquid water content
122 !
123 DO jlayer=1,io%NGROUND_LAYER
124  WRITE(ylvl,'(I2)') jlayer
125  yrecfm=hpatch//'GR_WG'//adjustl(ylvl(:len_trim(ylvl)))
126  yrecfm=adjustl(yrecfm)
127  CALL read_surf(hprogram,yrecfm,zwork(:),iresp)
128  pek%XWG(:,jlayer) = zwork
129 END DO
130 !
131 !* soil ice water content
132 !
133 DO jlayer=1,io%NGROUND_LAYER
134  WRITE(ylvl,'(I2)') jlayer
135  yrecfm=hpatch//'GR_WGI'//adjustl(ylvl(:len_trim(ylvl)))
136  yrecfm=adjustl(yrecfm)
137  CALL read_surf(hprogram,yrecfm,zwork(:),iresp)
138  pek%XWGI(:,jlayer) = zwork
139 END DO
140 !
141 !* water intercepted on leaves
142 !
143 yrecfm=hpatch//'GR_WR'
144 yrecfm=adjustl(yrecfm)
145  CALL read_surf(hprogram,yrecfm,pek%XWR(:),iresp)
146 !
147 !* Leaf Area Index
148 !
149 IF (io%CPHOTO=='NIT' .OR. io%CPHOTO=='NCB') THEN
150  yrecfm = hpatch//'GR_LAI'
151  yrecfm=adjustl(yrecfm)
152  CALL read_surf(hprogram,yrecfm,pek%XLAI(:),iresp)
153 END IF
154 !
155 !* snow mantel
156 !
157  CALL read_gr_snow(hprogram,'GR',hpatch,ilu,ilu,p%NR_P,0,pek%TSNOW )! IOO:GreenROOf
158 !
159 !-------------------------------------------------------------------------------
160 !
161 !* 4. Semi-prognostic variables
162 ! -------------------------
163 !
164 !* aerodynamical resistance
165 !
166 yrecfm = hpatch//'GR_RESA'
167 yrecfm=adjustl(yrecfm)
168 pek%XRESA(:) = 100.
169  CALL read_surf(hprogram,yrecfm,pek%XRESA(:),iresp)
170 !
171 pek%XLE(:) = xundef
172 !
173 !* ISBA-AGS variables
174 !
175 IF (io%CPHOTO/='NON') THEN
176  pek%XAN(:) = 0.
177  pek%XANDAY(:) = 0.
178  pek%XANFM(:) = xanfminit
179  pek%XLE(:) = 0.
180 END IF
181 !
182 IF (io%CPHOTO=='AST') THEN
183  pek%XBIOMASS(:,:) = 0.
184  pek%XRESP_BIOMASS(:,:) = 0.
185 ELSEIF (io%CPHOTO=='NIT') THEN
186  pek%XBIOMASS(:,:) = 0.
187  DO jnbiomass=1,io%NNBIOMASS
188  WRITE(ylvl,'(I1)') jnbiomass
189  yrecfm=hpatch//'GR_BIOMA'//adjustl(ylvl(:len_trim(ylvl)))
190  yrecfm=adjustl(yrecfm)
191  CALL read_surf(hprogram,yrecfm,pek%XBIOMASS(:,jnbiomass),iresp)
192  END DO
193 
194  pek%XRESP_BIOMASS(:,:) = 0.
195  DO jnbiomass=2,io%NNBIOMASS
196  WRITE(ylvl,'(I1)') jnbiomass
197  yrecfm=hpatch//'GR_RESPI'//adjustl(ylvl(:len_trim(ylvl)))
198  yrecfm=adjustl(yrecfm)
199  CALL read_surf(hprogram,yrecfm,pek%XRESP_BIOMASS(:,jnbiomass),iresp)
200  END DO
201 ENDIF
202 !
203 !
204 DEALLOCATE(zwork)
205 IF (lhook) CALL dr_hook('READ_TEB_GREENROOF_N',1,zhook_handle)
206 !
207 !-------------------------------------------------------------------------------
208 !
209 END SUBROUTINE read_teb_greenroof_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine read_teb_greenroof_n(DTCO, U, IO, P, PEK, HPROGRAM, HPA
subroutine read_gr_snow(HPROGRAM, HSURFTYPE, HPREFIX, KLU, KSIZE_P, KMASK_P, KPATCH, TPSNOW, HDI
Definition: read_gr_snow.F90:8