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

Last change on this file since 1821 was 1821, checked in by Ehouarn Millour, 11 years ago

Le passage de définition est maintenant effectué automatiquement lors du premier appel d'écriture à phys_output_write.
UG
.................................................
The definition run is now automatically triggered by the first writing call to phys_output_write.
UG

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