source: LMDZ5/trunk/libf/phylmd/phys_output_write_new.h @ 1792

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

Adding new version of phys_output_write and ctrlout_mod.
UG

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