SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
diag_townn.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 diag_town_n (DGL, DGT, U, &
7  hprogram, &
8  prn, ph, ple, plei, pgflux, pri, pcd, pch, pce, pqs,&
9  pz0, pz0h, pt2m, pts, pq2m, phu2m, pzon10m, pmer10m,&
10  pswd, pswu, pswbd, pswbu, plwd, plwu, pfmu, pfmv, &
11  prnc, phc, plec, pgfluxc, pswdc, pswuc, plwdc, &
12  plwuc, pfmuc, pfmvc, pt2m_min, pt2m_max, pleic, &
13  phu2m_min, phu2m_max, pwind10m, pwind10m_max, &
14  pevap, pevapc, psubl, psublc )
15 ! ######################################################################
16 !
17 !!**** *DIAG_TOWN_n * - Chooses the surface schemes for town diagnostics
18 !!
19 !! PURPOSE
20 !! -------
21 !
22 !!** METHOD
23 !! ------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2004
36 !! Modified 01/2006 : sea flux parameterization.
37 !! Modified 08/2009 : new diag
38 !! Modified 09/2012 : new PLEI diag required by atmospheric model
39 ! B. decharme 04/2013 : Add EVAP and SUBL diag
40 !!------------------------------------------------------------------
41 !
42 
43 !
44 !
45 !
46 !
48 USE modd_diag_teb_n, ONLY : diag_teb_t
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 USE modd_csts, ONLY : xtt, xlstt, xlvtt
53 !
54 USE modi_diag_teb_n
55 USE modi_diag_ideal_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 TYPE(diag_ideal_t), INTENT(INOUT) :: dgl
66 TYPE(diag_teb_t), INTENT(INOUT) :: dgt
67 TYPE(surf_atm_t), INTENT(INOUT) :: u
68 !
69  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
70 !
71 REAL, DIMENSION(:), INTENT(OUT) :: prn ! Net radiation (W/m2)
72 REAL, DIMENSION(:), INTENT(OUT) :: ph ! Sensible heat flux (W/m2)
73 REAL, DIMENSION(:), INTENT(OUT) :: ple ! Total latent heat flux (W/m2)
74 REAL, DIMENSION(:), INTENT(OUT) :: plei ! Sublimation latent heat flux (W/m2)
75 REAL, DIMENSION(:), INTENT(OUT) :: pgflux ! Storage flux (W/m2)
76 REAL, DIMENSION(:), INTENT(OUT) :: pevap ! Total evapotranspiration (kg/m2/s)
77 REAL, DIMENSION(:), INTENT(OUT) :: psubl ! Sublimation (kg/m2/s)
78 REAL, DIMENSION(:), INTENT(OUT) :: pri ! Richardson number (-)
79 REAL, DIMENSION(:), INTENT(OUT) :: pcd ! drag coefficient (W/s2)
80 REAL, DIMENSION(:), INTENT(OUT) :: pch ! transf. coef heat (W/s)
81 REAL, DIMENSION(:), INTENT(OUT) :: pce ! transf. coef vapor (W/s/K)
82 REAL, DIMENSION(:), INTENT(OUT) :: pqs
83 REAL, DIMENSION(:), INTENT(OUT) :: pz0 ! rough. length wind (m)
84 REAL, DIMENSION(:), INTENT(OUT) :: pz0h ! rough. length heat (m)
85 REAL, DIMENSION(:), INTENT(OUT) :: pts ! surface temperature (K)
86 REAL, DIMENSION(:), INTENT(OUT) :: pt2m ! temperature at 2m (K)
87 REAL, DIMENSION(:), INTENT(OUT) :: pq2m ! humidity at 2m (kg/kg)
88 REAL, DIMENSION(:), INTENT(OUT) :: phu2m ! relative humidity at 2m (-)
89 REAL, DIMENSION(:), INTENT(OUT) :: pzon10m ! zonal wind at 10m (m/s)
90 REAL, DIMENSION(:), INTENT(OUT) :: pmer10m ! meridian wind at 10m(m/s)
91 REAL, DIMENSION(:), INTENT(OUT) :: pswd ! incoming short wave radiation (W/m2)
92 REAL, DIMENSION(:), INTENT(OUT) :: pswu ! outgoing short wave radiation (W/m2)
93 REAL, DIMENSION(:,:), INTENT(OUT) :: pswbd ! incoming short wave radiation by spectral band(W/m2)
94 REAL, DIMENSION(:,:), INTENT(OUT) :: pswbu ! outgoing short wave radiation by spectral band(W/m2)
95 REAL, DIMENSION(:), INTENT(OUT) :: plwd ! incoming long wave radiation (W/m2)
96 REAL, DIMENSION(:), INTENT(OUT) :: plwu ! outgoing long wave radiation (W/m2)
97 REAL, DIMENSION(:), INTENT(OUT) :: pfmu ! zonal friction
98 REAL, DIMENSION(:), INTENT(OUT) :: pfmv ! meridian friction
99 REAL, DIMENSION(:), INTENT(OUT) :: prnc ! Net radiation (J/m2)
100 REAL, DIMENSION(:), INTENT(OUT) :: phc ! Sensible heat flux (J/m2)
101 REAL, DIMENSION(:), INTENT(OUT) :: plec ! Total latent heat flux (J/m2)
102 REAL, DIMENSION(:), INTENT(OUT) :: pleic ! Sublimation latent heat flux (J/m2)
103 REAL, DIMENSION(:), INTENT(OUT) :: pgfluxc ! Storage flux (J/m2)
104 REAL, DIMENSION(:), INTENT(OUT) :: pevapc ! Total evapotranspiration (kg/m2/s)
105 REAL, DIMENSION(:), INTENT(OUT) :: psublc ! Sublimation (kg/m2/s)
106 REAL, DIMENSION(:), INTENT(OUT) :: pswdc ! incoming short wave radiation (J/m2)
107 REAL, DIMENSION(:), INTENT(OUT) :: pswuc ! outgoing short wave radiation (J/m2)
108 REAL, DIMENSION(:), INTENT(OUT) :: plwdc ! incoming long wave radiation (J/m2)
109 REAL, DIMENSION(:), INTENT(OUT) :: plwuc ! outgoing long wave radiation (J/m2)
110 REAL, DIMENSION(:), INTENT(OUT) :: pfmuc ! zonal friction
111 REAL, DIMENSION(:), INTENT(OUT) :: pfmvc ! meridian friction
112 REAL, DIMENSION(:), INTENT(OUT) :: pt2m_min ! Minimum temperature at 2m (K)
113 REAL, DIMENSION(:), INTENT(OUT) :: pt2m_max ! Maximum temperature at 2m (K)
114 REAL, DIMENSION(:), INTENT(OUT) :: phu2m_min! Minimum relative humidity at 2m (-)
115 REAL, DIMENSION(:), INTENT(OUT) :: phu2m_max! Maximum relative humidity at 2m (-)
116 REAL, DIMENSION(:), INTENT(OUT) :: pwind10m ! wind at 10m (m/s)
117 REAL, DIMENSION(:), INTENT(OUT) :: pwind10m_max! Maximum wind at 10m (m/s)
118 !
119 !* 0.2 declarations of local variables
120 !
121 REAL, DIMENSION(SIZE(PRN)) :: zdelta
122 !
123 REAL(KIND=JPRB) :: zhook_handle
124 !-------------------------------------------------------------------------------------
125 !
126 IF (lhook) CALL dr_hook('DIAG_TOWN_N',0,zhook_handle)
127 IF (u%CTOWN=='TEB ') THEN
128  CALL diag_teb_n(dgt, &
129  hprogram, &
130  prn, ph, ple, pgflux, pri, pcd, pch, pce, pqs, &
131  pz0, pz0h, pt2m, pts, pq2m, phu2m, pzon10m, pmer10m,&
132  pswd, pswu, plwd, plwu, pswbd, pswbu, pfmu, pfmv, &
133  pt2m_min, pt2m_max, phu2m_min, phu2m_max, &
134  pwind10m, pwind10m_max )
135 !
136 !!!!! important, diagd should be computed in teb !!!!!!
137 !
138 ! diag not yet inplemeted for TEB (these diag are required for the climate model)
139 !
140 ! Ok with atmospheric model but LEI (latent heat of sublimation w/m2), EVAP (total evapotranspiration kg/m2/s),
141 ! and SUBL (sublimation kg/m2/s) must by implemented in TEB as well as theirs cumulative values
142 ! Not good if LCPL_ARP = TRUE in ISBA (ALARO)
143 !
144  IF (SIZE(plei)>0) THEN
145  plei(:) = xundef
146  pevap(:) = xundef
147  psubl(:) = xundef
148  WHERE(ple(:)/=xundef)
149  zdelta(:) = max(0.0,sign(1.0,xtt-pts(:)))
150  pevap(:) = (ple(:) * zdelta(:))/xlstt + (ple(:) * (1.0-zdelta(:)))/xlvtt
151  plei(:) = ple(:) * zdelta(:)
152  psubl(:) = plei(:)/xlstt
153  ENDWHERE
154  ENDIF
155 !
156  plec = xundef
157  pleic = xundef
158  pevapc = xundef
159  psublc = xundef
160  prnc = xundef
161  phc = xundef
162  pgfluxc = xundef
163  pswdc = xundef
164  pswuc = xundef
165  plwdc = xundef
166  plwuc = xundef
167  pfmuc = xundef
168  pfmvc = xundef
169 !
170 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
171 !
172 ELSE IF (u%CTOWN=='FLUX ') THEN
173  CALL diag_ideal_n(dgl, hprogram, &
174  prn, ph, ple, plei, pgflux, pri, pcd, pch, pce, pqs,&
175  pz0, pz0h, pt2m, pts, pq2m, phu2m, pzon10m, pmer10m,&
176  pswd, pswu, plwd, plwu, pswbd, pswbu, pfmu, pfmv, &
177  prnc, phc, plec, pgfluxc, pswdc, pswuc, plwdc, &
178  plwuc, pfmuc, pfmvc, pt2m_min, pt2m_max, pleic, &
179  phu2m_min, phu2m_max, pwind10m, pwind10m_max, &
180  pevap, pevapc, psubl, psublc )
181 ELSE IF (u%CTOWN=='NONE ') THEN
182  prn = xundef
183  ph = xundef
184  ple = xundef
185  plei = xundef
186  pevap = xundef
187  psubl = xundef
188  pgflux = xundef
189  pri = xundef
190  pcd = xundef
191  pch = xundef
192  pce = xundef
193  pqs = xundef
194  pz0 = xundef
195  pz0h = xundef
196  pts = xundef
197  pt2m = xundef
198  pq2m = xundef
199  phu2m = xundef
200  pzon10m = xundef
201  pmer10m = xundef
202  pswd = xundef
203  pswu = xundef
204  pswbd = xundef
205  pswbu = xundef
206  plwd = xundef
207  plwu = xundef
208  pfmu = xundef
209  pfmv = xundef
210  prnc = xundef
211  phc = xundef
212  plec = xundef
213  pleic = xundef
214  pevapc = xundef
215  psublc = xundef
216  pgfluxc = xundef
217  pswdc = xundef
218  pswuc = xundef
219  plwdc = xundef
220  plwuc = xundef
221  pfmuc = xundef
222  pfmvc = xundef
223  pt2m_min = xundef
224  pt2m_max = xundef
225  phu2m_min= xundef
226  phu2m_max= xundef
227  pwind10m = xundef
228  pwind10m_max = xundef
229 END IF
230 IF (lhook) CALL dr_hook('DIAG_TOWN_N',1,zhook_handle)
231 !
232 !-------------------------------------------------------------------------------------
233 !
234 END SUBROUTINE diag_town_n
subroutine diag_ideal_n(DGL, HPROGRAM, PRN, PH, PLE, PLEI, PGFLUX, PRI, PCD, PCH, PCE, PQS, PZ0, PZ0H, PT2M, PTS, PQ2M, PHU2M, PZON10M, PMER10M, PSWD, PSWU, PLWD, PLWU, PSWBD, PSWBU, PFMU, PFMV, PRNC, PHC, PLEC, PGFLUXC, PSWDC, PSWUC, PLWDC, PLWUC, PFMUC, PFMVC, PT2M_MIN, PT2M_MAX, PLEIC, PHU2M_MIN, PHU2M_MAX, PWIND10M, PWIND10M_MAX, PEVAP, PEVAPC, PSUBL, PSUBLC)
Definition: diag_idealn.F90:6
subroutine diag_town_n(DGL, DGT, U, HPROGRAM, PRN, PH, PLE, PLEI, PGFLUX, PRI, PCD, PCH, PCE, PQS, PZ0, PZ0H, PT2M, PTS, PQ2M, PHU2M, PZON10M, PMER10M, PSWD, PSWU, PSWBD, PSWBU, PLWD, PLWU, PFMU, PFMV, PRNC, PHC, PLEC, PGFLUXC, PSWDC, PSWUC, PLWDC, PLWUC, PFMUC, PFMVC, PT2M_MIN, PT2M_MAX, PLEIC, PHU2M_MIN, PHU2M_MAX, PWIND10M, PWIND10M_MAX, PEVAP, PEVAPC, PSUBL, PSUBLC)
Definition: diag_townn.F90:6
subroutine diag_teb_n(DGT, HPROGRAM, PRN, PH, PLE, PGFLUX, PRI, PCD, PCH, PCE, PQS, PZ0, PZ0H, PT2M, PTS, PQ2M, PHU2M, PZON10M, PMER10M, PSWD, PSWU, PLWD, PLWU, PSWBD, PSWBU, PFMU, PFMV, PT2M_MIN, PT2M_MAX, PHU2M_MIN, PHU2M_MAX, PWIND10M, PWIND10M_MAX)
Definition: diag_tebn.F90:6