source: LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90 @ 1813

Last change on this file since 1813 was 1813, checked in by idelkadi, 11 years ago
  1. transform phytrac into a module, in order to pass some variables

(tracer tendencies) to the standard physiq ouput codes.

  1. Correct a (big) bug in the call to phytrac.
  2. Include w*, and ALEs in the call to phytrac and traclmdz.

physiq.F

  • Bug correction in the call of phytrac from the physics u10m,v10m, ustar -> zu10m, zv10m, zustar

phytrac.F90 -> phytrac_mod.F90

  • Tranformation of routine phytrac into a module phytrac_mod, in order to tranfer the tracer tendencies from phytrac to

phys_output...

  • Inclusion of w*, Ale bl/wake in the call to phytrac and traclmdz

(to be used for dust emmission)

by respectively, vertical diffusion, thermal plumes and convection

  • desactivation of ini_histrac.h and write_histrac.h
  • USE phys_output_mod removed since it was creating a circular

dependency

between phytrac_mod and phys_output_mod.
So the automatic computation of ecrit_tra is desactivated

ini_histrac.h and write_histrac.h

Descactivated in phytrac but kept for backard compatibility
couchelimite -> iflag_vdf_trac>0

phys_output_ctrlout_mod.F90

New variables : o_dtr_vdf, o_dtr_the ... for output of tracer tendencies

phys_output_mod.F90

Default definition for these new output variables.

phys_output_write_F90.h

disapears, included directly in phys_output_write_mod.F90

phys_output_write_mod.F90

writing of the tracer tendencies

phys_state_var_mod.F90

New declaration (wstar)

traclmdz_mod.F90

  • Inclusion of w*, Ale bl/wake in the call to phytrac and traclmdz

(to be used for dust emmission)

File size: 36.8 KB
Line 
1!
2! $Header$
3!
4MODULE phys_output_write_mod
5
6    USE phytrac_mod, ONLY : d_tr_cl, d_tr_th, d_tr_cv, d_tr_lessi_impa, &
7        d_tr_lessi_nucl, d_tr_insc, d_tr_bcscav, d_tr_evapls, d_tr_ls,  &
8        d_tr_trsp, d_tr_sscav, d_tr_sat, d_tr_uscav
9
10
11! Author: Abderrahmane IDELKADI (original include file)
12! Author: Laurent FAIRHEAD (transformation to module/subroutine)
13! Author: Ulysse GERARD (effective implementation)
14
15
16   CONTAINS
17     
18! ug Routine pour définir (los du premier passageà) ET sortir les variables
19    SUBROUTINE phys_output_write(itap, pdtphys, paprs, pphis, &
20   &                  pplay, lmax_th, aerosol_couple,         &
21   &                  ok_ade, ok_aie, ivap, new_aod, ok_sync, &
22   &                  ptconv, read_climoz, clevSTD, ptconvth, &
23   &                  d_t, qx, d_qx, zmasse, flag_aerosol_strat)
24
25! This subroutine does the actual writing of diagnostics that were
26! defined and initialised in phys_output_mod.F90
27
28    USE dimphy
29    USE control_mod
30    USE phys_output_ctrlout_mod
31    USE phys_state_var_mod
32    USE phys_local_var_mod
33    USE indice_sol_mod
34    USE infotrac
35    USE comgeomphy
36    USE surface_data,     ONLY : type_ocean, ok_veget
37    USE aero_mod
38    USE ioipsl
39    USE write_field_phy
40    USE iophy
41
42    IMPLICIT NONE
43
44    INCLUDE "temps.h"
45    INCLUDE "clesphys.h"
46    INCLUDE "thermcell.h"
47    INCLUDE "compbl.h"
48    INCLUDE "YOMCST.h"
49    INCLUDE "dimensions.h"
50
51! Input
52    INTEGER :: itap, ivap, read_climoz
53    INTEGER, DIMENSION(klon) :: lmax_th
54    LOGICAL :: aerosol_couple, ok_sync
55    LOGICAL :: ok_ade, ok_aie, new_aod
56    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
57    REAL :: pdtphys
58    CHARACTER (LEN=4), DIMENSION(nlevSTD) :: clevSTD
59    REAL, DIMENSION(klon) :: pphis
60    REAL, DIMENSION(klon, klev) :: pplay, d_t
61    REAL, DIMENSION(klon, klev+1) :: paprs
62    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
63    REAL, DIMENSION(klon, llm) :: zmasse
64    LOGICAL :: flag_aerosol_strat
65
66! Local
67    INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
68    INTEGER :: itau_w
69    INTEGER :: i, iff, iq, nsrf, k, ll, naero
70    REAL, DIMENSION (klon) :: zx_tmp_fi2d
71    REAL, DIMENSION (klon,klev) :: zx_tmp_fi3d, zpt_conv
72    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
73    CHARACTER (LEN=4)              :: bb2
74    INTEGER, DIMENSION(iim*jjmp1)  :: ndex2d
75    INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
76    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
77
78    IF(vars_defined) THEN
79! On calcul le nouveau tau:
80     itau_w = itau_phy + itap + start_time * day_step / iphysiq
81! On le donne à iophy pour que les histwrite y aient accès:
82     CALL set_itau_iophy(itau_w)
83    ENDIF
84
85! On procède à l'écriture ou à la définition des nombreuses variables:
86!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
87      CALL histwrite_phy(o_phis, pphis)
88      CALL histwrite_phy(o_aire, airephy)
89
90IF (itap > 0) THEN
91      DO i=1, klon
92       zx_tmp_fi2d(i)=pctsrf(i,is_ter)+pctsrf(i,is_lic)
93      ENDDO
94ENDIF
95
96      CALL histwrite_phy(o_contfracATM, zx_tmp_fi2d)
97      CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
98      CALL histwrite_phy(o_aireTER, paire_ter)
99!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
100      CALL histwrite_phy(o_flat, zxfluxlat)
101      CALL histwrite_phy(o_slp, slp)
102      CALL histwrite_phy(o_tsol, zxtsol)
103      CALL histwrite_phy(o_t2m, zt2m)
104      CALL histwrite_phy(o_t2m_min, zt2m)
105      CALL histwrite_phy(o_t2m_max, zt2m)
106
107IF (itap > 0) THEN
108      DO i=1, klon
109       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
110      ENDDO
111ENDIF
112      CALL histwrite_phy(o_wind10m, zx_tmp_fi2d)
113
114IF (itap > 0) THEN
115      DO i=1, klon
116       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
117      ENDDO
118ENDIF
119      CALL histwrite_phy(o_wind10max, zx_tmp_fi2d)
120
121IF (itap > 0) THEN
122      DO i = 1, klon
123         zx_tmp_fi2d(i) = pctsrf(i,is_sic)
124      ENDDO
125ENDIF
126      CALL histwrite_phy(o_sicf, zx_tmp_fi2d)
127      CALL histwrite_phy(o_q2m, zq2m)
128      CALL histwrite_phy(o_ustar, zustar)
129      CALL histwrite_phy(o_u10m, zu10m)
130      CALL histwrite_phy(o_v10m, zv10m)
131
132IF (itap > 0) THEN
133      DO i = 1, klon
134         zx_tmp_fi2d(i) = paprs(i,1)
135      ENDDO
136ENDIF
137      CALL histwrite_phy(o_psol, zx_tmp_fi2d)
138      CALL histwrite_phy(o_mass, zmasse)
139      CALL histwrite_phy(o_qsurf, zxqsurf)
140
141IF (.NOT. ok_veget) THEN
142      CALL histwrite_phy(o_qsol, qsol)
143ENDIF
144
145IF (itap > 0) THEN
146       DO i = 1, klon
147         zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
148       ENDDO
149ENDIF
150
151      CALL histwrite_phy(o_precip, zx_tmp_fi2d)
152      CALL histwrite_phy(o_ndayrain, nday_rain)
153
154IF (itap > 0) THEN
155       DO i = 1, klon
156         zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
157       ENDDO
158ENDIF
159      CALL histwrite_phy(o_plul, zx_tmp_fi2d)
160
161IF (itap > 0) THEN
162      DO i = 1, klon
163         zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
164      ENDDO
165ENDIF
166      CALL histwrite_phy(o_pluc, zx_tmp_fi2d)
167      CALL histwrite_phy(o_snow, snow_fall)
168      CALL histwrite_phy(o_msnow, snow_o)
169      CALL histwrite_phy(o_fsnow, zfra_o)
170      CALL histwrite_phy(o_evap, evap)
171      CALL histwrite_phy(o_tops, topsw)
172      CALL histwrite_phy(o_tops0, topsw0)
173      CALL histwrite_phy(o_topl, toplw)
174      CALL histwrite_phy(o_topl0, toplw0)
175
176IF (itap > 0) THEN
177      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, klevp1 )
178ENDIF
179      CALL histwrite_phy(o_SWupTOA, zx_tmp_fi2d)
180
181IF (itap > 0) THEN
182      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, klevp1 )
183ENDIF
184      CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
185
186IF (itap > 0) THEN
187      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, klevp1 )
188ENDIF
189      CALL histwrite_phy(o_SWdnTOA, zx_tmp_fi2d)
190
191IF (itap > 0) THEN
192      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, klevp1 )
193ENDIF
194      CALL histwrite_phy(o_SWdnTOAclr, zx_tmp_fi2d)
195
196IF (itap > 0) THEN
197      zx_tmp_fi2d(:) = topsw(:)-toplw(:)
198ENDIF
199      CALL histwrite_phy(o_nettop, zx_tmp_fi2d)
200      CALL histwrite_phy(o_SWup200, SWup200)
201      CALL histwrite_phy(o_SWup200clr, SWup200clr)
202      CALL histwrite_phy(o_SWdn200, SWdn200)
203      CALL histwrite_phy(o_SWdn200clr, SWdn200clr)
204      CALL histwrite_phy(o_LWup200, LWup200)
205      CALL histwrite_phy(o_LWup200clr, LWup200clr)
206      CALL histwrite_phy(o_LWdn200, LWdn200)
207      CALL histwrite_phy(o_LWdn200clr, LWdn200clr)
208      CALL histwrite_phy(o_sols, solsw)
209      CALL histwrite_phy(o_sols0, solsw0)
210      CALL histwrite_phy(o_soll, sollw)
211      CALL histwrite_phy(o_radsol, radsol)
212      CALL histwrite_phy(o_soll0, sollw0)
213
214IF (itap > 0) THEN
215      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, 1 )
216ENDIF
217      CALL histwrite_phy(o_SWupSFC, zx_tmp_fi2d)
218
219IF (itap > 0) THEN
220      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, 1 )
221ENDIF
222      CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
223
224IF (itap > 0) THEN
225      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, 1 )
226ENDIF
227      CALL histwrite_phy(o_SWdnSFC, zx_tmp_fi2d)
228
229IF (itap > 0) THEN
230      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, 1 )
231ENDIF
232      CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
233
234IF (itap > 0) THEN
235      zx_tmp_fi2d(1:klon)=sollwdown(1:klon)-sollw(1:klon)
236ENDIF
237      CALL histwrite_phy(o_LWupSFC, zx_tmp_fi2d)
238      CALL histwrite_phy(o_LWdnSFC, sollwdown)
239
240IF (itap > 0) THEN
241       sollwdownclr(1:klon) = -1.*lwdn0(1:klon,1)
242      zx_tmp_fi2d(1:klon)=sollwdownclr(1:klon)-sollw0(1:klon)
243ENDIF
244      CALL histwrite_phy(o_LWupSFCclr, zx_tmp_fi2d)
245      CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
246      CALL histwrite_phy(o_bils, bils)
247      CALL histwrite_phy(o_bils_diss, bils_diss)
248      CALL histwrite_phy(o_bils_ec, bils_ec)
249      CALL histwrite_phy(o_bils_tke, bils_tke)
250      CALL histwrite_phy(o_bils_kinetic, bils_kinetic)
251      CALL histwrite_phy(o_bils_latent, bils_latent)
252      CALL histwrite_phy(o_bils_enthalp, bils_enthalp)
253
254IF (itap > 0) THEN
255      zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
256ENDIF
257      CALL histwrite_phy(o_sens, zx_tmp_fi2d)
258      CALL histwrite_phy(o_fder, fder)
259      CALL histwrite_phy(o_ffonte, zxffonte)
260      CALL histwrite_phy(o_fqcalving, zxfqcalving)
261      CALL histwrite_phy(o_fqfonte, zxfqfonte)
262IF (itap > 0) THEN
263      zx_tmp_fi2d=0.
264      DO nsrf=1,nbsrf
265        zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxu(:,1,nsrf)
266      ENDDO
267ENDIF
268      CALL histwrite_phy(o_taux, zx_tmp_fi2d)
269
270IF (itap > 0) THEN
271      zx_tmp_fi2d=0.
272      DO nsrf=1,nbsrf
273          zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxv(:,1,nsrf)
274      ENDDO
275ENDIF
276      CALL histwrite_phy(o_tauy, zx_tmp_fi2d)
277
278
279         DO nsrf = 1, nbsrf
280IF (itap > 0)             zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
281      CALL histwrite_phy(o_pourc_srf(nsrf), zx_tmp_fi2d)
282IF (itap > 0)           zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
283      CALL histwrite_phy(o_fract_srf(nsrf), zx_tmp_fi2d)
284IF (itap > 0)         zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
285      CALL histwrite_phy(o_taux_srf(nsrf), zx_tmp_fi2d)
286IF (itap > 0)         zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
287      CALL histwrite_phy(o_tauy_srf(nsrf), zx_tmp_fi2d)
288IF (itap > 0)         zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
289      CALL histwrite_phy(o_tsol_srf(nsrf), zx_tmp_fi2d)
290IF (itap > 0)         zx_tmp_fi2d(1 : klon) = evap_pot( 1 : klon, nsrf)
291      CALL histwrite_phy(o_evappot_srf(nsrf), zx_tmp_fi2d)
292IF (itap > 0)       zx_tmp_fi2d(1 : klon) = ustar(1 : klon, nsrf)
293      CALL histwrite_phy(o_ustar_srf(nsrf), zx_tmp_fi2d)
294IF (itap > 0)       zx_tmp_fi2d(1 : klon) = u10m(1 : klon, nsrf)
295      CALL histwrite_phy(o_u10m_srf(nsrf), zx_tmp_fi2d)
296IF (itap > 0)       zx_tmp_fi2d(1 : klon) = v10m(1 : klon, nsrf)
297      CALL histwrite_phy(o_v10m_srf(nsrf), zx_tmp_fi2d)
298IF (itap > 0)       zx_tmp_fi2d(1 : klon) = t2m(1 : klon, nsrf)
299      CALL histwrite_phy(o_t2m_srf(nsrf), zx_tmp_fi2d)
300IF (itap > 0)       zx_tmp_fi2d(1 : klon) = fevap(1 : klon, nsrf)
301      CALL histwrite_phy(o_evap_srf(nsrf), zx_tmp_fi2d)
302IF (itap > 0)        zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
303      CALL histwrite_phy(o_sens_srf(nsrf), zx_tmp_fi2d)
304IF (itap > 0)         zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
305      CALL histwrite_phy(o_lat_srf(nsrf), zx_tmp_fi2d)
306IF (itap > 0)         zx_tmp_fi2d(1 : klon) = fsollw( 1 : klon, nsrf)
307      CALL histwrite_phy(o_flw_srf(nsrf), zx_tmp_fi2d)
308IF (itap > 0)         zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, nsrf)
309      CALL histwrite_phy(o_fsw_srf(nsrf), zx_tmp_fi2d)
310IF (itap > 0)         zx_tmp_fi2d(1 : klon) = wfbils( 1 : klon, nsrf)
311      CALL histwrite_phy(o_wbils_srf(nsrf), zx_tmp_fi2d)
312IF (itap > 0)         zx_tmp_fi2d(1 : klon) = wfbilo( 1 : klon, nsrf)
313      CALL histwrite_phy(o_wbilo_srf(nsrf), zx_tmp_fi2d)
314
315      IF (iflag_pbl > 1) THEN
316      CALL histwrite_phy(o_tke_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
317      CALL histwrite_phy(o_tke_max_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
318      ENDIF
319
320      ENDDO
321      CALL histwrite_phy(o_cdrm, cdragm)
322      CALL histwrite_phy(o_cdrh, cdragh)
323      CALL histwrite_phy(o_cldl, cldl)
324      CALL histwrite_phy(o_cldm, cldm)
325      CALL histwrite_phy(o_cldh, cldh)
326      CALL histwrite_phy(o_cldt, cldt)
327      CALL histwrite_phy(o_cldq, cldq)
328IF (itap > 0)       zx_tmp_fi2d(1:klon) = flwp(1:klon)
329      CALL histwrite_phy(o_lwp, zx_tmp_fi2d)
330IF (itap > 0)       zx_tmp_fi2d(1:klon) = fiwp(1:klon)
331      CALL histwrite_phy(o_iwp, zx_tmp_fi2d)
332      CALL histwrite_phy(o_ue, ue)
333      CALL histwrite_phy(o_ve, ve)
334      CALL histwrite_phy(o_uq, uq)
335      CALL histwrite_phy(o_vq, vq)
336      IF(iflag_con.GE.3) THEN ! sb
337      CALL histwrite_phy(o_cape, cape)
338      CALL histwrite_phy(o_pbase, ema_pcb)
339      CALL histwrite_phy(o_ptop, ema_pct)
340      CALL histwrite_phy(o_fbase, ema_cbmf)
341        if (iflag_con /= 30) then
342      CALL histwrite_phy(o_plcl, plcl)
343      CALL histwrite_phy(o_plfc, plfc)
344      CALL histwrite_phy(o_wbeff, wbeff)
345        end if
346
347      CALL histwrite_phy(o_cape_max, cape)
348
349      CALL histwrite_phy(o_upwd, upwd)
350      CALL histwrite_phy(o_Ma, Ma)
351      CALL histwrite_phy(o_dnwd, dnwd)
352      CALL histwrite_phy(o_dnwd0, dnwd0)
353IF (itap > 0)         zx_tmp_fi2d=float(itau_con)/float(itap)
354      CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
355IF (itap > 0) THEN
356      IF(iflag_thermals>=1)THEN
357         zx_tmp_fi3d=dnwd+dnwd0+upwd+fm_therm(:,1:klev)
358      ELSE
359         zx_tmp_fi3d=dnwd+dnwd0+upwd
360      ENDIF
361ENDIF
362      CALL histwrite_phy(o_mc, zx_tmp_fi3d)
363      ENDIF !iflag_con .GE. 3
364      CALL histwrite_phy(o_prw, prw)
365      CALL histwrite_phy(o_s_pblh, s_pblh)
366      CALL histwrite_phy(o_s_pblt, s_pblt)
367      CALL histwrite_phy(o_s_lcl, s_lcl)
368      CALL histwrite_phy(o_s_therm, s_therm)
369!IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
370!       IF (o_s_capCL%flag(iff)<=lev_files(iff)) THEN
371!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
372!    $o_s_capCL%name,itau_w,s_capCL)
373!       ENDIF
374!       IF (o_s_oliqCL%flag(iff)<=lev_files(iff)) THEN
375!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
376!    $o_s_oliqCL%name,itau_w,s_oliqCL)
377!       ENDIF
378!       IF (o_s_cteiCL%flag(iff)<=lev_files(iff)) THEN
379!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
380!    $o_s_cteiCL%name,itau_w,s_cteiCL)
381!       ENDIF
382!       IF (o_s_trmb1%flag(iff)<=lev_files(iff)) THEN
383!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
384!    $o_s_trmb1%name,itau_w,s_trmb1)
385!       ENDIF
386!       IF (o_s_trmb2%flag(iff)<=lev_files(iff)) THEN
387!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
388!    $o_s_trmb2%name,itau_w,s_trmb2)
389!       ENDIF
390!       IF (o_s_trmb3%flag(iff)<=lev_files(iff)) THEN
391!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
392!    $o_s_trmb3%name,itau_w,s_trmb3)
393!       ENDIF
394
395
396
397! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
398! Champs interpolles sur des niveaux de pression
399      DO iff=1, nfiles
400        ll=0
401        DO k=1, nlevSTD
402         bb2=clevSTD(k)
403         IF(bb2.EQ."850".OR.bb2.EQ."700".OR. &
404            bb2.EQ."500".OR.bb2.EQ."200".OR. &
405            bb2.EQ."100".OR. &
406            bb2.EQ."50".OR.bb2.EQ."10") THEN
407
408! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
409          ll=ll+1
410      CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
411      CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
412      CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
413      CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
414      CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
415      CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
416
417       ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
418       ENDDO
419       ENDDO
420
421
422
423IF (itap > 0) THEN
424      DO i=1, klon
425       IF (pctsrf(i,is_oce).GT.epsfra.OR. &
426           pctsrf(i,is_sic).GT.epsfra) THEN
427        zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ &
428                         ftsol(i, is_sic) * pctsrf(i,is_sic))/ &
429                         (pctsrf(i,is_oce)+pctsrf(i,is_sic))
430       ELSE
431        zx_tmp_fi2d(i) = 273.15
432       ENDIF
433      ENDDO
434ENDIF
435      CALL histwrite_phy(o_t_oce_sic, zx_tmp_fi2d)
436
437! Couplage convection-couche limite
438      IF (iflag_con.GE.3) THEN
439      IF (iflag_coupl>=1) THEN
440      CALL histwrite_phy(o_ale_bl, ale_bl)
441      CALL histwrite_phy(o_alp_bl, alp_bl)
442      ENDIF !iflag_coupl>=1
443      ENDIF !(iflag_con.GE.3)
444! Wakes
445      IF (iflag_con.EQ.3) THEN
446      IF (iflag_wake>=1) THEN
447      CALL histwrite_phy(o_ale_wk, ale_wake)
448      CALL histwrite_phy(o_alp_wk, alp_wake)
449      CALL histwrite_phy(o_ale, ale)
450      CALL histwrite_phy(o_alp, alp)
451      CALL histwrite_phy(o_cin, cin)
452      CALL histwrite_phy(o_WAPE, wake_pe)
453      CALL histwrite_phy(o_wake_h, wake_h)
454      CALL histwrite_phy(o_wake_s, wake_s)
455      CALL histwrite_phy(o_wake_deltat, wake_deltat)
456      CALL histwrite_phy(o_wake_deltaq, wake_deltaq)
457      CALL histwrite_phy(o_wake_omg, wake_omg)
458IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_wake(1:klon,1:klev) &
459                                              /pdtphys
460      CALL histwrite_phy(o_dtwak, zx_tmp_fi3d)
461IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_wake(1:klon,1:klev)/pdtphys
462      CALL histwrite_phy(o_dqwak, zx_tmp_fi3d)
463      ENDIF ! iflag_wake>=1
464      CALL histwrite_phy(o_Vprecip, Vprecip)
465      CALL histwrite_phy(o_ftd, ftd)
466      CALL histwrite_phy(o_fqd, fqd)
467      ELSEIF (iflag_con.EQ.30) THEN
468! sortie RomP convection descente insaturee iflag_con=30
469      CALL histwrite_phy(o_Vprecip, Vprecip)
470      CALL histwrite_phy(o_wdtrainA, wdtrainA)
471      CALL histwrite_phy(o_wdtrainM, wdtrainM)
472      ENDIF !(iflag_con.EQ.3.or.iflag_con.EQ.30)
473!!! nrlmd le 10/04/2012
474        IF (iflag_trig_bl>=1) THEN
475      CALL histwrite_phy(o_n2, n2)
476      CALL histwrite_phy(o_s2, s2)
477      CALL histwrite_phy(o_proba_notrig, proba_notrig)
478      CALL histwrite_phy(o_random_notrig, random_notrig)
479      CALL histwrite_phy(o_ale_bl_stat, ale_bl_stat)
480      CALL histwrite_phy(o_ale_bl_trig, ale_bl_trig)
481       ENDIF  !(iflag_trig_bl>=1)
482        IF (iflag_clos_bl>=1) THEN
483      CALL histwrite_phy(o_alp_bl_det, alp_bl_det)
484      CALL histwrite_phy(o_alp_bl_fluct_m, alp_bl_fluct_m)
485      CALL histwrite_phy(o_alp_bl_fluct_tke,  &
486       alp_bl_fluct_tke)
487      CALL histwrite_phy(o_alp_bl_conv, alp_bl_conv)
488      CALL histwrite_phy(o_alp_bl_stat, alp_bl_stat)
489       ENDIF  !(iflag_clos_bl>=1)
490!!! fin nrlmd le 10/04/2012
491      IF (type_ocean=='slab ') THEN
492      CALL histwrite_phy(o_slab_bils, slab_wfbils)
493      ENDIF !type_ocean == force/slab
494      CALL histwrite_phy(o_weakinv, weak_inversion)
495      CALL histwrite_phy(o_dthmin, dthmin)
496      CALL histwrite_phy(o_cldtau, cldtau)
497      CALL histwrite_phy(o_cldemi, cldemi)
498      CALL histwrite_phy(o_pr_con_l, pmflxr(:,1:klev))
499      CALL histwrite_phy(o_pr_con_i, pmflxs(:,1:klev))
500      CALL histwrite_phy(o_pr_lsc_l, prfl(:,1:klev))
501      CALL histwrite_phy(o_pr_lsc_i, psfl(:,1:klev))
502      CALL histwrite_phy(o_re, re)
503      CALL histwrite_phy(o_fl, fl)
504IF (itap > 0) THEN
505      DO i=1, klon
506       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
507      ENDDO
508ENDIF
509      CALL histwrite_phy(o_rh2m, zx_tmp_fi2d)
510
511IF (itap > 0) THEN
512      DO i=1, klon
513       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
514      ENDDO
515ENDIF
516      CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
517
518IF (itap > 0) THEN
519      DO i=1, klon
520       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
521      ENDDO
522ENDIF
523      CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
524
525      CALL histwrite_phy(o_qsat2m, qsat2m)
526      CALL histwrite_phy(o_tpot, tpot)
527      CALL histwrite_phy(o_tpote, tpote)
528IF (itap > 0) zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, is_ter)
529      CALL histwrite_phy(o_SWnetOR,  zx_tmp_fi2d)
530IF (itap > 0) zx_tmp_fi2d(1:klon) = solsw(1:klon)/(1.-albsol1(1:klon))
531      CALL histwrite_phy(o_SWdownOR,  zx_tmp_fi2d)
532      CALL histwrite_phy(o_LWdownOR, sollwdown)
533      CALL histwrite_phy(o_snowl, snow_lsc)
534      CALL histwrite_phy(o_solldown, sollwdown)
535      CALL histwrite_phy(o_dtsvdfo, d_ts(:,is_oce))
536      CALL histwrite_phy(o_dtsvdft, d_ts(:,is_ter))
537      CALL histwrite_phy(o_dtsvdfg,  d_ts(:,is_lic))
538      CALL histwrite_phy(o_dtsvdfi, d_ts(:,is_sic))
539      CALL histwrite_phy(o_rugs, zxrugs)
540! OD550 per species
541      IF (new_aod .and. (.not. aerosol_couple)) THEN
542          IF (ok_ade.OR.ok_aie) THEN
543      CALL histwrite_phy(o_od550aer, od550aer)
544      CALL histwrite_phy(o_od865aer, od865aer)
545      CALL histwrite_phy(o_absvisaer, absvisaer)
546      CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
547      CALL histwrite_phy(o_sconcso4, sconcso4)
548      CALL histwrite_phy(o_sconcoa, sconcoa)
549      CALL histwrite_phy(o_sconcbc, sconcbc)
550      CALL histwrite_phy(o_sconcss, sconcss)
551      CALL histwrite_phy(o_sconcdust, sconcdust)
552      CALL histwrite_phy(o_concso4, concso4)
553      CALL histwrite_phy(o_concoa, concoa)
554      CALL histwrite_phy(o_concbc, concbc)
555      CALL histwrite_phy(o_concss, concss)
556      CALL histwrite_phy(o_concdust, concdust)
557      CALL histwrite_phy(o_loadso4, loadso4)
558      CALL histwrite_phy(o_loadoa, loadoa)
559      CALL histwrite_phy(o_loadbc, loadbc)
560      CALL histwrite_phy(o_loadss, loadss)
561      CALL histwrite_phy(o_loaddust, loaddust)
562!--STRAT AER
563          ENDIF
564          IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN
565          DO naero = 1, naero_spc
566      CALL histwrite_phy(o_tausumaero(naero), &
567       tausum_aero(:,2,naero) )
568          END DO
569          ENDIF
570      ENDIF
571       IF (ok_ade) THEN
572      CALL histwrite_phy(o_topswad, topswad_aero)
573      CALL histwrite_phy(o_topswad0, topswad0_aero)
574      CALL histwrite_phy(o_solswad, solswad_aero)
575      CALL histwrite_phy(o_solswad0, solswad0_aero)
576!====MS forcing diagnostics
577        if (new_aod) then
578      CALL histwrite_phy(o_swtoaas_nat, topsw_aero(:,1))
579      CALL histwrite_phy(o_swsrfas_nat, solsw_aero(:,1))
580      CALL histwrite_phy(o_swtoacs_nat, topsw0_aero(:,1))
581      CALL histwrite_phy(o_swsrfcs_nat, solsw0_aero(:,1))
582!ant
583      CALL histwrite_phy(o_swtoaas_ant, topsw_aero(:,2))
584      CALL histwrite_phy(o_swsrfas_ant, solsw_aero(:,2))
585      CALL histwrite_phy(o_swtoacs_ant, topsw0_aero(:,2))
586      CALL histwrite_phy(o_swsrfcs_ant, solsw0_aero(:,2))
587!cf
588        if (.not. aerosol_couple) then
589      CALL histwrite_phy(o_swtoacf_nat, topswcf_aero(:,1))
590      CALL histwrite_phy(o_swsrfcf_nat, solswcf_aero(:,1))
591      CALL histwrite_phy(o_swtoacf_ant, topswcf_aero(:,2))
592      CALL histwrite_phy(o_swsrfcf_ant, solswcf_aero(:,2))
593      CALL histwrite_phy(o_swtoacf_zero,topswcf_aero(:,3))
594      CALL histwrite_phy(o_swsrfcf_zero,solswcf_aero(:,3))
595        endif
596    endif ! new_aod
597!====MS forcing diagnostics
598       ENDIF
599       IF (ok_aie) THEN
600      CALL histwrite_phy(o_topswai, topswai_aero)
601      CALL histwrite_phy(o_solswai, solswai_aero)
602      CALL histwrite_phy(o_scdnc, scdnc)
603      CALL histwrite_phy(o_cldncl, cldncl)
604      CALL histwrite_phy(o_reffclws, reffclws)
605      CALL histwrite_phy(o_reffclwc, reffclwc)
606      CALL histwrite_phy(o_cldnvi, cldnvi)
607      CALL histwrite_phy(o_lcc, lcc)
608      CALL histwrite_phy(o_lcc3d, lcc3d)
609      CALL histwrite_phy(o_lcc3dcon, lcc3dcon)
610      CALL histwrite_phy(o_lcc3dstra, lcc3dstra)
611      CALL histwrite_phy(o_reffclwtop, reffclwtop)
612       ENDIF
613! Champs 3D:
614       IF (ok_ade .OR. ok_aie) then
615      CALL histwrite_phy(o_ec550aer, ec550aer)
616       ENDIF
617      CALL histwrite_phy(o_lwcon, flwc)
618      CALL histwrite_phy(o_iwcon, fiwc)
619      CALL histwrite_phy(o_temp, t_seri)
620      CALL histwrite_phy(o_theta, theta)
621      CALL histwrite_phy(o_ovapinit, qx(:,:,ivap))
622      CALL histwrite_phy(o_ovap, q_seri)
623      CALL histwrite_phy(o_oliq, ql_seri)
624      CALL histwrite_phy(o_geop, zphi)
625      CALL histwrite_phy(o_vitu, u_seri)
626      CALL histwrite_phy(o_vitv, v_seri)
627      CALL histwrite_phy(o_vitw, omega)
628      CALL histwrite_phy(o_pres, pplay)
629      CALL histwrite_phy(o_paprs, paprs(:,1:klev))
630IF (itap > 0) THEN
631         DO i=1, klon
632          zx_tmp_fi3d1(i,1)= pphis(i)/RG
633!020611   zx_tmp_fi3d(i,1)= pphis(i)/RG
634         ENDDO
635         DO k=1, klev
636!020611        DO k=1, klev-1
637         DO i=1, klon
638!020611         zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - (t_seri(i,k) *RD *
639          zx_tmp_fi3d1(i,k+1)= zx_tmp_fi3d1(i,k) - (t_seri(i,k) *RD *  &
640          (paprs(i,k+1) - paprs(i,k))) / ( pplay(i,k) * RG )
641         ENDDO
642         ENDDO
643ENDIF
644      CALL histwrite_phy(o_zfull,zx_tmp_fi3d1(:,2:klevp1))
645!020611    $o_zfull%name,itau_w,zx_tmp_fi3d)
646
647IF (itap > 0)  THEN
648         DO i=1, klon
649          zx_tmp_fi3d(i,1)= pphis(i)/RG - ( &
650          (t_seri(i,1)+zxtsol(i))/2. *RD * &
651          (pplay(i,1) - paprs(i,1)))/( (paprs(i,1)+pplay(i,1))/2.* RG)
652         ENDDO
653         DO k=1, klev-1
654         DO i=1, klon
655          zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - ( &
656          (t_seri(i,k)+t_seri(i,k+1))/2. *RD *  &
657          (pplay(i,k+1) - pplay(i,k))) / ( paprs(i,k) * RG )
658         ENDDO
659         ENDDO
660ENDIF
661      CALL histwrite_phy(o_zhalf, zx_tmp_fi3d)
662      CALL histwrite_phy(o_rneb, cldfra)
663      CALL histwrite_phy(o_rnebcon, rnebcon)
664      CALL histwrite_phy(o_rnebls, rneb)
665      CALL histwrite_phy(o_rhum, zx_rh)
666      CALL histwrite_phy(o_ozone, &
667       wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
668
669      IF (read_climoz == 2) THEN
670      CALL histwrite_phy(o_ozone_light, &
671       wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
672      ENDIF
673
674      CALL histwrite_phy(o_dtphy, d_t)
675      CALL histwrite_phy(o_dqphy,  d_qx(:,:,ivap))
676        DO nsrf=1, nbsrf
677IF (itap > 0) zx_tmp_fi2d(1 : klon) = falb1( 1 : klon, nsrf)
678      CALL histwrite_phy(o_albe_srf(nsrf), zx_tmp_fi2d)
679IF (itap > 0) zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)
680      CALL histwrite_phy(o_rugs_srf(nsrf), zx_tmp_fi2d)
681IF (itap > 0) zx_tmp_fi2d(1 : klon) = agesno( 1 : klon, nsrf)
682      CALL histwrite_phy(o_ages_srf(nsrf), zx_tmp_fi2d)
683        ENDDO !nsrf=1, nbsrf
684      CALL histwrite_phy(o_alb1, albsol1)
685      CALL histwrite_phy(o_alb2, albsol2)
686!FH Sorties pour la couche limite
687      if (iflag_pbl>1) then
688      zx_tmp_fi3d=0.
689IF (itap > 0) THEN
690      do nsrf=1,nbsrf
691         do k=1,klev
692          zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
693          +pctsrf(:,nsrf)*pbl_tke(:,k,nsrf)
694         enddo
695      enddo
696ENDIF
697      CALL histwrite_phy(o_tke, zx_tmp_fi3d)
698
699      CALL histwrite_phy(o_tke_max, zx_tmp_fi3d)
700      ENDIF
701
702      CALL histwrite_phy(o_kz, coefh(:,:,is_ave))
703
704      CALL histwrite_phy(o_kz_max, coefh(:,:,is_ave))
705
706      CALL histwrite_phy(o_clwcon, clwcon0)
707      CALL histwrite_phy(o_dtdyn, d_t_dyn)
708      CALL histwrite_phy(o_dqdyn, d_q_dyn)
709      CALL histwrite_phy(o_dudyn, d_u_dyn)
710      CALL histwrite_phy(o_dvdyn, d_v_dyn)
711
712IF (itap > 0) THEN
713      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys
714ENDIF
715      CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
716      if(iflag_thermals.eq.1)then
717IF (itap > 0) THEN
718      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
719                                 d_t_ajsb(1:klon,1:klev)/pdtphys
720ENDIF
721      CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
722      else if(iflag_thermals.gt.1.and.iflag_wake.EQ.1)then
723IF (itap > 0) THEN
724      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
725                                 d_t_ajs(1:klon,1:klev)/pdtphys + &
726                                 d_t_wake(1:klon,1:klev)/pdtphys
727ENDIF
728      CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
729      endif
730IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
731      CALL histwrite_phy(o_ducon, zx_tmp_fi3d)
732IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_v_con(1:klon,1:klev)/pdtphys
733      CALL histwrite_phy(o_dvcon, zx_tmp_fi3d)
734IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
735      CALL histwrite_phy(o_dqcon, zx_tmp_fi3d)
736
737      IF(iflag_thermals.EQ.1) THEN
738IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
739        CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
740      ELSE IF(iflag_thermals.GT.1.AND.iflag_wake.EQ.1) THEN
741IF (itap > 0) THEN
742         zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + &
743                                     d_q_ajs(1:klon,1:klev)/pdtphys + &
744                                     d_q_wake(1:klon,1:klev)/pdtphys
745ENDIF
746         CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
747      ENDIF
748
749IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_lsc(1:klon,1:klev)/pdtphys
750      CALL histwrite_phy(o_dtlsc, zx_tmp_fi3d)
751IF (itap > 0) zx_tmp_fi3d(1:klon, 1:klev)=(d_t_lsc(1:klon,1:klev)+ &
752                                 d_t_eva(1:klon,1:klev))/pdtphys
753      CALL histwrite_phy(o_dtlschr, zx_tmp_fi3d)
754IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys
755      CALL histwrite_phy(o_dqlsc, zx_tmp_fi3d)
756IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=beta_prec(1:klon,1:klev)
757      CALL histwrite_phy(o_beta_prec, zx_tmp_fi3d)
758!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
759! Sorties specifiques a la separation thermiques/non thermiques
760       if (iflag_thermals>=1) then
761IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscth(1:klon,1:klev)/pdtphys
762      CALL histwrite_phy(o_dtlscth, zx_tmp_fi3d)
763IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscst(1:klon,1:klev)/pdtphys
764      CALL histwrite_phy(o_dtlscst, zx_tmp_fi3d)
765IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscth(1:klon,1:klev)/pdtphys
766      CALL histwrite_phy(o_dqlscth, zx_tmp_fi3d)
767IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscst(1:klon,1:klev)/pdtphys
768      CALL histwrite_phy(o_dqlscst, zx_tmp_fi3d)
769      CALL histwrite_phy(o_plulth, plul_th)
770      CALL histwrite_phy(o_plulst, plul_st)
771IF (itap > 0) THEN
772      do k=1,klev
773      do i=1,klon
774          if (ptconvth(i,k)) then
775           zx_tmp_fi3d(i,k)=1.
776          else
777           zx_tmp_fi3d(i,k)=0.
778          endif
779      enddo
780      enddo
781ENDIF
782      CALL histwrite_phy(o_ptconvth, zx_tmp_fi3d)
783IF (itap > 0) THEN
784      do i=1,klon
785           zx_tmp_fi2d(1:klon)=lmax_th(:)
786      enddo
787ENDIF
788      CALL histwrite_phy(o_lmaxth, zx_tmp_fi2d)
789      endif ! iflag_thermals>=1
790!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
791IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf(1:klon,1:klev)/pdtphys
792      CALL histwrite_phy(o_dtvdf, zx_tmp_fi3d)
793IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_diss(1:klon,1:klev)/pdtphys
794      CALL histwrite_phy(o_dtdis, zx_tmp_fi3d)
795IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf(1:klon,1:klev)/pdtphys
796      CALL histwrite_phy(o_dqvdf, zx_tmp_fi3d)
797IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_eva(1:klon,1:klev)/pdtphys
798      CALL histwrite_phy(o_dteva, zx_tmp_fi3d)
799IF (itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_eva(1:klon,1:klev)/pdtphys
800      CALL histwrite_phy(o_dqeva, zx_tmp_fi3d)
801      zpt_conv = 0.
802      WHERE (ptconv) zpt_conv = 1.
803      CALL histwrite_phy(o_ptconv, zpt_conv)
804      CALL histwrite_phy(o_ratqs, ratqs)
805IF (itap > 0) THEN
806      zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys - &
807                                 d_t_ajsb(1:klon,1:klev)/pdtphys
808ENDIF
809      CALL histwrite_phy(o_dtthe, zx_tmp_fi3d)
810       IF (iflag_thermals>=1) THEN
811! Pour l instant 0 a y reflichir pour les thermiques
812         zx_tmp_fi2d=0.
813      CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
814      CALL histwrite_phy(o_f_th, fm_therm)
815      CALL histwrite_phy(o_e_th, entr_therm)
816      CALL histwrite_phy(o_w_th, zw2)
817      CALL histwrite_phy(o_q_th, zqasc)
818      CALL histwrite_phy(o_a_th, fraca)
819      CALL histwrite_phy(o_d_th, detr_therm)
820      CALL histwrite_phy(o_f0_th, f0)
821      CALL histwrite_phy(o_zmax_th, zmax_th)
822IF (itap > 0) THEN
823      zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys - &
824                                 d_q_ajsb(1:klon,1:klev)/pdtphys
825ENDIF
826      CALL histwrite_phy(o_dqthe, zx_tmp_fi3d)
827      ENDIF !iflag_thermals
828IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_ajsb(1:klon,1:klev)/pdtphys
829      CALL histwrite_phy(o_dtajs, zx_tmp_fi3d)
830IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_q_ajsb(1:klon,1:klev)/pdtphys
831      CALL histwrite_phy(o_dqajs, zx_tmp_fi3d)
832IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY
833      CALL histwrite_phy(o_dtswr, zx_tmp_fi3d)
834IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=heat0(1:klon,1:klev)/RDAY
835      CALL histwrite_phy(o_dtsw0, zx_tmp_fi3d)
836IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=-1.*cool(1:klon,1:klev)/RDAY
837      CALL histwrite_phy(o_dtlwr, zx_tmp_fi3d)
838IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=-1.*cool0(1:klon,1:klev)/RDAY
839      CALL histwrite_phy(o_dtlw0, zx_tmp_fi3d)
840IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)/pdtphys
841      CALL histwrite_phy(o_dtec, zx_tmp_fi3d)
842IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_u_vdf(1:klon,1:klev)/pdtphys
843      CALL histwrite_phy(o_duvdf, zx_tmp_fi3d)
844IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_v_vdf(1:klon,1:klev)/pdtphys
845      CALL histwrite_phy(o_dvvdf, zx_tmp_fi3d)
846       IF (ok_orodr) THEN
847IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_u_oro(1:klon,1:klev)/pdtphys
848      CALL histwrite_phy(o_duoro, zx_tmp_fi3d)
849IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_v_oro(1:klon,1:klev)/pdtphys
850      CALL histwrite_phy(o_dvoro, zx_tmp_fi3d)
851IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_oro(1:klon,1:klev)/pdtphys
852      CALL histwrite_phy(o_dtoro, zx_tmp_fi3d)
853       ENDIF
854        IF (ok_orolf) THEN
855IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_u_lif(1:klon,1:klev)/pdtphys
856      CALL histwrite_phy(o_dulif, zx_tmp_fi3d)
857       ENDIF
858IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_v_lif(1:klon,1:klev)/pdtphys
859      CALL histwrite_phy(o_dvlif, zx_tmp_fi3d)
860
861IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_lif(1:klon,1:klev)/pdtphys
862      CALL histwrite_phy(o_dtlif, zx_tmp_fi3d)
863
864       IF (ok_hines) THEN
865IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_u_hin(1:klon,1:klev)/pdtphys
866      CALL histwrite_phy(o_duhin, zx_tmp_fi3d)
867IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_v_hin(1:klon,1:klev)/pdtphys
868      CALL histwrite_phy(o_dvhin, zx_tmp_fi3d)
869IF(itap > 0) zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys
870      CALL histwrite_phy(o_dthin, zx_tmp_fi3d)
871        ENDIF
872      CALL histwrite_phy(o_rsu, swup)
873      CALL histwrite_phy(o_rsd, swdn)
874      CALL histwrite_phy(o_rlu, lwup)
875      CALL histwrite_phy(o_rld, lwdn)
876      CALL histwrite_phy(o_rsucs, swup0)
877      CALL histwrite_phy(o_rsdcs, swdn0)
878      CALL histwrite_phy(o_rlucs, lwup0)
879      CALL histwrite_phy(o_rldcs, lwdn0)
880IF(itap > 0) THEN
881      zx_tmp_fi3d(1:klon,1:klev)=d_t(1:klon,1:klev)+ &
882      d_t_dyn(1:klon,1:klev)
883ENDIF
884      CALL histwrite_phy(o_tnt, zx_tmp_fi3d)
885IF(itap > 0) THEN
886      zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY - &
887      cool(1:klon,1:klev)/RDAY
888ENDIF
889      CALL histwrite_phy(o_tntr, zx_tmp_fi3d)
890IF(itap > 0) THEN
891      zx_tmp_fi3d(1:klon,1:klev)= (d_t_lsc(1:klon,1:klev)+ &
892                                   d_t_eva(1:klon,1:klev)+ &
893                                   d_t_vdf(1:klon,1:klev))/pdtphys
894ENDIF
895      CALL histwrite_phy(o_tntscpbl, zx_tmp_fi3d)
896IF(itap > 0) THEN
897      zx_tmp_fi3d(1:klon,1:klev)=d_qx(1:klon,1:klev,ivap)+ &
898      d_q_dyn(1:klon,1:klev)
899ENDIF
900      CALL histwrite_phy(o_tnhus, zx_tmp_fi3d)
901IF(itap > 0) THEN
902      zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys+ &
903                                 d_q_eva(1:klon,1:klev)/pdtphys
904ENDIF
905      CALL histwrite_phy(o_tnhusscpbl, zx_tmp_fi3d)
906      CALL histwrite_phy(o_evu, coefm(:,:,is_ave))
907IF(itap > 0) THEN
908      zx_tmp_fi3d(1:klon,1:klev)=q_seri(1:klon,1:klev)+ &
909                                 ql_seri(1:klon,1:klev)
910ENDIF
911      CALL histwrite_phy(o_h2o, zx_tmp_fi3d)
912       if (iflag_con >= 3) then
913IF(itap > 0) THEN
914             zx_tmp_fi3d(1:klon,1:klev)=-1 * (dnwd(1:klon,1:klev)+ &
915                  dnwd0(1:klon,1:klev))
916ENDIF
917      CALL histwrite_phy(o_mcd, zx_tmp_fi3d)
918IF(itap > 0) THEN
919             zx_tmp_fi3d(1:klon,1:klev)=upwd(1:klon,1:klev) + &
920                  dnwd(1:klon,1:klev)+ dnwd0(1:klon,1:klev)
921ENDIF
922      CALL histwrite_phy(o_dmc, zx_tmp_fi3d)
923       else if (iflag_con == 2) then
924      CALL histwrite_phy(o_mcd,  pmfd)
925      CALL histwrite_phy(o_dmc,  pmfu + pmfd)
926       end if
927      CALL histwrite_phy(o_ref_liq, ref_liq)
928      CALL histwrite_phy(o_ref_ice, ref_ice)
929      if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
930       RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
931       RCFC12_per.NE.RCFC12_act) THEN
932IF(itap > 0) zx_tmp_fi2d(1 : klon) = swupp ( 1 : klon, klevp1 )
933      CALL histwrite_phy(o_rsut4co2, zx_tmp_fi2d)
934IF(itap > 0) zx_tmp_fi2d(1 : klon) = lwupp ( 1 : klon, klevp1 )
935      CALL histwrite_phy(o_rlut4co2, zx_tmp_fi2d)
936IF(itap > 0) zx_tmp_fi2d(1 : klon) = swup0p ( 1 : klon, klevp1 )
937      CALL histwrite_phy(o_rsutcs4co2, zx_tmp_fi2d)
938IF(itap > 0) zx_tmp_fi2d(1 : klon) = lwup0p ( 1 : klon, klevp1 )
939      CALL histwrite_phy(o_rlutcs4co2, zx_tmp_fi2d)
940      CALL histwrite_phy(o_rsu4co2, swupp)
941      CALL histwrite_phy(o_rlu4co2, lwupp)
942      CALL histwrite_phy(o_rsucs4co2, swup0p)
943      CALL histwrite_phy(o_rlucs4co2, lwup0p)
944      CALL histwrite_phy(o_rsd4co2, swdnp)
945      CALL histwrite_phy(o_rld4co2, lwdnp)
946      CALL histwrite_phy(o_rsdcs4co2, swdn0p)
947      CALL histwrite_phy(o_rldcs4co2, lwdn0p)
948      ENDIF
949        IF (nqtot.GE.3) THEN
950         DO iq=3,nqtot
951             CALL histwrite_phy(o_trac(iq-2), qx(:,:,iq))
952             CALL histwrite_phy(o_dtr_vdf(iq-2),d_tr_cl(:,:,iq-2))
953             CALL histwrite_phy(o_dtr_the(iq-2),d_tr_th(:,:,iq-2))
954             CALL histwrite_phy(o_dtr_con(iq-2),d_tr_cv(:,:,iq-2))
955             CALL histwrite_phy(o_dtr_lessi_impa(iq-2),d_tr_lessi_impa(:,:,iq-2))
956             CALL histwrite_phy(o_dtr_lessi_nucl(iq-2),d_tr_lessi_nucl(:,:,iq-2))
957             CALL histwrite_phy(o_dtr_insc(iq-2),d_tr_insc(:,:,iq-2))
958             CALL histwrite_phy(o_dtr_bcscav(iq-2),d_tr_bcscav(:,:,iq-2))
959             CALL histwrite_phy(o_dtr_evapls(iq-2),d_tr_evapls(:,:,iq-2))
960             CALL histwrite_phy(o_dtr_ls(iq-2),d_tr_ls(:,:,iq-2))
961             CALL histwrite_phy(o_dtr_trsp(iq-2),d_tr_trsp(:,:,iq-2))
962             CALL histwrite_phy(o_dtr_sscav(iq-2),d_tr_sscav(:,:,iq-2))
963             CALL histwrite_phy(o_dtr_sat(iq-2),d_tr_sat(:,:,iq-2))
964             CALL histwrite_phy(o_dtr_uscav(iq-2),d_tr_uscav(:,:,iq-2))
965         zx_tmp_fi2d=0.
966IF(itap > 0) THEN
967         DO k=1,klev
968            zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*qx(:,k,iq)
969         ENDDO
970ENDIF
971            CALL histwrite_phy(o_trac_cum(iq-2), zx_tmp_fi2d)
972         ENDDO
973        ENDIF
974
975
976    IF(vars_defined) THEN
977! On synchronise les fichiers pour IOIPSL
978      DO iff=1,nfiles
979          IF (ok_sync .AND. clef_files(iff)) THEN
980!$OMP MASTER
981              CALL histsync(nid_files(iff))
982!$OMP END MASTER
983          ENDIF
984      END DO
985
986    ELSE
987    vars_defined = .TRUE.
988    ENDIF
989
990     
991
992
993    END SUBROUTINE phys_output_write
994
995
996
997  END MODULE phys_output_write_mod
998
Note: See TracBrowser for help on using the repository browser.