SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_teb_canopyn.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_canopy_n (DTCO, U, TCP, TOP, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *READ_TEB_CANOPY_n* - reads TEB fields
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 01/2003
37 !! E. Martin 01/2012 Add LSBL_COLD_START
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
47 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 !
54 USE modi_canopy_grid
55 USE modi_get_type_dim_n
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 Declarations of arguments
63 ! -------------------------
64 !
65 !
66 TYPE(data_cover_t), INTENT(INOUT) :: dtco
67 TYPE(surf_atm_t), INTENT(INOUT) :: u
68 TYPE(teb_canopy_t), INTENT(INOUT) :: tcp
69 TYPE(teb_options_t), INTENT(INOUT) :: top
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
72 !
73 !
74 !* 0.2 Declarations of local variables
75 ! -------------------------------
76 !
77 !
78  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
79  CHARACTER(LEN=3) :: yread
80 INTEGER :: jlayer ! loop counter on layers
81 INTEGER :: ilu ! 1D physical dimension
82 INTEGER :: iresp ! Error code after redding
83 INTEGER :: iversion, ibugfix ! surface version
84 REAL(KIND=JPRB) :: zhook_handle
85 !-------------------------------------------------------------------------------
86 !
87 !* 1D physical dimension
88 !
89 IF (lhook) CALL dr_hook('READ_TEB_CANOPY_N',0,zhook_handle)
90 yrecfm='SIZE_TOWN'
91  CALL get_type_dim_n(dtco, u, &
92  'TOWN ',ilu)
93 !
94 !* flag to use or not canopy levels
95 !
96 yrecfm='VERSION'
97  CALL read_surf(&
98  hprogram,yrecfm,iversion,iresp)
99 !
100 yrecfm='BUG'
101  CALL read_surf(&
102  hprogram,yrecfm,ibugfix,iresp)
103 !
104 IF (iversion<3) THEN
105  top%LCANOPY = .false.
106 ELSE
107  yrecfm='TEB_CANOPY'
108  CALL read_surf(&
109  hprogram,yrecfm,top%LCANOPY,iresp)
110 END IF
111 !
112 IF (.NOT.top%LCANOPY) THEN
113  ALLOCATE(tcp%XZ (0,0))
114  ALLOCATE(tcp%XU (0,0))
115  ALLOCATE(tcp%XT (0,0))
116  ALLOCATE(tcp%XQ (0,0))
117  ALLOCATE(tcp%XTKE(0,0))
118  ALLOCATE(tcp%XLMO(0,0))
119  ALLOCATE(tcp%XP (0,0))
120  ALLOCATE(tcp%XLM (0,0))
121  ALLOCATE(tcp%XLEPS(0,0))
122  ALLOCATE(tcp%XDZ (0,0))
123  ALLOCATE(tcp%XZF (0,0))
124  ALLOCATE(tcp%XDZF(0,0))
125  IF (lhook) CALL dr_hook('READ_TEB_CANOPY_N',1,zhook_handle)
126  RETURN
127 ENDIF
128 !
129 !* number of vertical levels
130 !
131 yrecfm='TEB_CAN_LVL'
132  CALL read_surf(&
133  hprogram,yrecfm,tcp%NLVL,iresp)
134 !
135 !* 2. Prognostic fields:
136 ! -----------------
137 !
138 !* altitudes
139 !
140 ALLOCATE(tcp%XZ(ilu,tcp%NLVL))
141 !
142 DO jlayer=1,tcp%NLVL
143  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_Z',jlayer,' '
144  CALL read_surf(&
145  hprogram,yrecfm,tcp%XZ(:,jlayer),iresp)
146 END DO
147 !
148 ALLOCATE(tcp%XU (ilu,tcp%NLVL))
149 ALLOCATE(tcp%XT (ilu,tcp%NLVL))
150 ALLOCATE(tcp%XQ (ilu,tcp%NLVL))
151 ALLOCATE(tcp%XTKE(ilu,tcp%NLVL))
152 ALLOCATE(tcp%XLMO(ilu,tcp%NLVL))
153 ALLOCATE(tcp%XP (ilu,tcp%NLVL))
154 !
155 IF (iversion>7 .OR. iversion==7 .AND.ibugfix>=2) THEN
156  yrecfm='STORAGETYPE'
157  CALL read_surf(&
158  hprogram,yrecfm,yread,iresp)
159 ELSE
160  yread = 'ALL'
161 ENDIF
162 !
163 IF(yread=='ALL') THEN
164  !
165  !* wind in SBL
166  DO jlayer=1,tcp%NLVL
167  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_U',jlayer,' '
168  CALL read_surf(&
169  hprogram,yrecfm,tcp%XU(:,jlayer),iresp)
170  END DO
171  !
172  !* theta in SBL
173  DO jlayer=1,tcp%NLVL
174  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_T',jlayer,' '
175  CALL read_surf(&
176  hprogram,yrecfm,tcp%XT(:,jlayer),iresp)
177  END DO
178  !
179  !* humidity in SBL
180  DO jlayer=1,tcp%NLVL
181  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_Q',jlayer,' '
182  CALL read_surf(&
183  hprogram,yrecfm,tcp%XQ(:,jlayer),iresp)
184  END DO
185  !
186  !* Tke in SBL
187  DO jlayer=1,tcp%NLVL
188  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_E',jlayer,' '
189  CALL read_surf(&
190  hprogram,yrecfm,tcp%XTKE(:,jlayer),iresp)
191  END DO
192  !
193  !* Monin-Obhukov length
194  IF (iversion<7) THEN
195  yrecfm='TEB_CAN_LMO '
196  CALL read_surf(&
197  hprogram,yrecfm,tcp%XLMO(:,1),iresp)
198  DO jlayer = 2,tcp%NLVL
199  tcp%XLMO(:,jlayer) = tcp%XLMO(:,1)
200  ENDDO
201  ELSE
202  DO jlayer=1,tcp%NLVL
203  WRITE(yrecfm,'(A10,I2.2)') 'TEB_CAN_MO',jlayer
204  CALL read_surf(&
205  hprogram,yrecfm,tcp%XLMO(:,jlayer),iresp)
206  ENDDO
207  ENDIF
208  !
209  !* Pressure
210  DO jlayer=1,tcp%NLVL
211  WRITE(yrecfm,'(A9,I2.2,A1)') 'TEB_CAN_P',jlayer,' '
212  CALL read_surf(&
213  hprogram,yrecfm,tcp%XP(:,jlayer),iresp)
214  END DO
215  !
216 ELSE
217  tcp%XU (:,:) = xundef
218  tcp%XT (:,:) = xundef
219  tcp%XQ (:,:) = xundef
220  tcp%XTKE(:,:) = xundef
221  tcp%XLMO(:,:) = xundef
222  tcp%XP (:,:) = xundef
223 ENDIF
224 !
225 !* mixing length
226 !
227 ALLOCATE(tcp%XLM(ilu,tcp%NLVL))
228 !
229 !* dissipative length
230 !
231 ALLOCATE(tcp%XLEPS(ilu,tcp%NLVL))
232 !
233 !
234 !* Grid characteristics
235 !
236 !
237 ! --------------------------------- XZ(k+1) XDZ(k+1)
238 ! ^
239 ! |
240 ! |
241 ! - - - - - - - - - - - - - - - - - XZf(k+1) | XDZf(k+1)
242 ! ^ |
243 ! | |
244 ! --------------------------------- XZ(k), XU, XT, XQ, XTKE | XDZ(k) V
245 ! | ^
246 ! - - - - - - - - - - - - - - - - - XZf(k) V | XDZf(k)
247 ! --------------------------------- XZ(k-1) XDZ(k-1) V
248 ! - - - - - - - - - - - - - - - - - XZf(k-1)
249 !
250 ALLOCATE(tcp%XDZ (ilu,tcp%NLVL))
251 ALLOCATE(tcp%XZF (ilu,tcp%NLVL))
252 ALLOCATE(tcp%XDZF(ilu,tcp%NLVL))
253  CALL canopy_grid(ilu,tcp%NLVL,tcp%XZ,tcp%XZF,tcp%XDZ,tcp%XDZF)
254 !
255 IF (lhook) CALL dr_hook('READ_TEB_CANOPY_N',1,zhook_handle)
256 !-------------------------------------------------------------------------------
257 !
258 END SUBROUTINE read_teb_canopy_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine canopy_grid(KI, KLVL, PZ, PZF, PDZ, PDZF)
Definition: canopy_grid.F90:6
subroutine read_teb_canopy_n(DTCO, U, TCP, TOP, HPROGRAM)