source: LMDZ5/branches/LF-private/libf/phylmd/phys_output_write_mod.F90 @ 2942

Last change on this file since 2942 was 1865, checked in by Laurent Fairhead, 11 years ago

Inclusion de la bibliothèque SISVAT/MAR à LMDZ pour le traitement des surfaces
"land ice"

  1. Menegoz

Integration of the SISVAT/MAR library to LMDZ to model the land ice surfaces

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