source: lmdz_wrf/WRFV3/lmdz/phys_output_write_new.h @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

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