Ignore:
Timestamp:
Feb 22, 2021, 12:44:07 PM (4 years ago)
Author:
dcugnet
Message:

Update the branch to the current trunk.

Location:
LMDZ6/branches/LMDZ-tracers
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-tracers

  • LMDZ6/branches/LMDZ-tracers/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r3630 r3851  
    6868       flux_sparam_sscoa,u10m_ss,v10m_ss
    6969
    70   USE dustemission_mod, ONLY : m1dflux, m2dflux, m3dflux
     70  USE dustemission_mod, ONLY : m1dflux, m2dflux, m3dflux 
    7171
    7272!  USE phytrac_mod, ONLY : d_tr_cl, d_tr_th, d_tr_cv, d_tr_lessi_impa, &
     
    8282CONTAINS
    8383
    84   ! ug Routine pour définir (los du premier passageà) ET sortir les variables
     84  ! ug Routine pour définir (lors du premier passageà) ET sortir les variables
    8585  SUBROUTINE phys_output_write_spl(itap, pdtphys, paprs, pphis, &
    8686       pplay, lmax_th, aerosol_couple,         &
     
    9090
    9191    ! This subroutine does the actual writing of diagnostics that were
    92     ! defined and initialised in phys_output_mod.F90
     92    ! defined and initialised mainly in phytracr_spl_mod.F90 (SPLA tracers, subroutine phytracr_spl_out_init)
    9393
    9494    USE dimphy, ONLY: klon, klev, klevp1
     
    148148         o_alp_bl_fluct_m, o_alp_bl_fluct_tke, &
    149149         o_alp_bl_conv, o_alp_bl_stat, &
    150          o_slab_qflux, o_tslab, o_slab_bils, &
     150         o_slab_qflux, o_tslab, &
     151         !o_slab_bils, &
    151152         o_slab_bilg, o_slab_sic, o_slab_tice, &
    152153         o_weakinv, o_dthmin, o_cldtau, &
    153154         o_cldemi, o_pr_con_l, o_pr_con_i, &
    154155         o_pr_lsc_l, o_pr_lsc_i, o_re, o_fl, &
    155          o_rh2m, o_rh2m_min, o_rh2m_max, &
     156         o_rh2m, &
     157         !o_rh2m_min, o_rh2m_max, &
    156158         o_qsat2m, o_tpot, o_tpote, o_SWnetOR, &
    157159         o_LWdownOR, o_snowl, &
    158160         o_solldown, o_dtsvdfo, o_dtsvdft, &
    159161         o_dtsvdfg, o_dtsvdfi, o_z0m, o_z0h, o_od550aer, &
    160          o_od865aer, o_absvisaer, o_od550lt1aer, &
     162         o_od865aer, o_abs550aer, o_od550lt1aer, &
    161163         o_sconcso4, o_sconcno3, o_sconcoa, o_sconcbc, &
    162164         o_sconcss, o_sconcdust, o_concso4, o_concno3, &
     
    300302         ema_cbmf, Ma, fm_therm, ale_bl, alp_bl, ale, &
    301303         alp, cin, wake_pe, wake_s, wake_deltat, &
     304         ale_wake, ale_bl_stat, &
    302305         wake_deltaq, ftd, fqd, ale_bl_trig, albsol1, &
    303306         rnebcon, wo, falb1, albsol2, coefh, clwcon0, &
     
    323326         t2m, fluxt, fluxlat, fsollw, fsolsw, &
    324327         wfbils, wfbilo, cdragm, cdragh, cldl, cldm, &
    325          cldh, cldt, JrNt, cldljn, cldmjn, cldhjn, &
    326          cldtjn, cldq, flwp, fiwp, ue, ve, uq, vq, &
     328         cldh, cldt, JrNt, &
     329         ! cldljn, cldmjn, cldhjn, cldtjn &
     330         cldq, flwp, fiwp, ue, ve, uq, vq, &
    327331         plcl, plfc, wbeff, upwd, dnwd, dnwd0, prw, &
    328332         s_pblh, s_pblt, s_lcl, s_therm, uwriteSTD, &
    329333         vwriteSTD, wwriteSTD, phiwriteSTD, qwriteSTD, &
    330          twriteSTD, ale_wake, alp_wake, wake_h, &
     334         twriteSTD, alp_wake, wake_h, &
     335         !ale_wake, &
    331336         wake_omg, d_t_wake, d_q_wake, Vprecip, &
    332337         wdtrainA, wdtrainM, n2, s2, proba_notrig, &
    333          random_notrig, ale_bl_stat, &
     338         random_notrig, &
     339         !ale_bl_stat, &
    334340         alp_bl_det, alp_bl_fluct_m, alp_bl_conv, &
    335341         alp_bl_stat, alp_bl_fluct_tke, slab_wfbils, &
     
    337343         pmflxr, pmflxs, prfl, psfl, re, fl, rh2m, &
    338344         qsat2m, tpote, tpot, d_ts, od550aer, &
    339          od865aer, absvisaer, od550lt1aer, sconcso4, sconcno3, &
     345         od865aer, abs550aer, od550lt1aer, sconcso4, sconcno3, &
    340346         sconcoa, sconcbc, sconcss, sconcdust, concso4, concno3, &
    341347         concoa, concbc, concss, concdust, loadso4, &
     
    372378         bils_ec,bils_ech, bils_tke, bils_kinetic, bils_latent, bils_enthalp, &
    373379         itau_con, nfiles, clef_files, nid_files, zvstr_gwd_rando
    374     USE ocean_slab_mod, ONLY: tslab, slab_bils, slab_bilg, tice, seaice
     380    USE ocean_slab_mod, ONLY: tslab, slab_bilg, tice, seaice
    375381    USE pbl_surface_mod, ONLY: snow
    376382    USE indice_sol_mod, ONLY: nbsrf
    377383    USE infotrac, ONLY: nqtot, nqo, nbtr, type_trac
    378384    USE geometry_mod, ONLY: cell_area
    379     USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, ok_snow
     385    USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, landice_opt
    380386!    USE aero_mod, ONLY: naero_spc
    381387    USE aero_mod, ONLY: naero_tot, id_STRAT_phy
     
    405411    INTEGER, DIMENSION(klon) :: lmax_th
    406412    LOGICAL :: aerosol_couple, ok_sync
     413    LOGICAL :: ok_ade, ok_aie
    407414    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
    408415    REAL :: pdtphys
     
    442449    CALL set_itau_iophy(itau_w)
    443450
    444     IF (.NOT.vars_defined) THEN
    445        iinitend = 2
    446     ELSE
    447        iinitend = 1
    448     ENDIF
     451!AS, vu avec LF : le test est fait maintenant au debut du pdt, pas a la fin, alors on ne passe plus qu'une fois
     452! Donc le "IF (.NOT.vars_defined)" devient inutile, et la boucle "DO iinit=1, iinitend" pourra etre eliminee
     453!  ainsi que iinit, iinitend
     454!    IF (.NOT.vars_defined) THEN
     455!       iinitend = 2
     456!    ELSE
     457!       iinitend = 1
     458!    ENDIF
    449459
    450460    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
     
    667677       CALL histwrite_phy(o_tauy, zx_tmp_fi2d)
    668678
    669        IF (ok_snow) THEN
     679       IF (landice_opt .GE. 1 ) THEN
    670680          CALL histwrite_phy(o_snowsrf, snow_o)
    671681          CALL histwrite_phy(o_qsnow, qsnow)
     
    735745       CALL histwrite_phy(o_cldt, cldt)
    736746       CALL histwrite_phy(o_JrNt, JrNt)
    737        CALL histwrite_phy(o_cldljn, cldl*JrNt)
    738        CALL histwrite_phy(o_cldmjn, cldm*JrNt)
    739        CALL histwrite_phy(o_cldhjn, cldh*JrNt)
    740        CALL histwrite_phy(o_cldtjn, cldt*JrNt)
     747
     748       !CALL histwrite_phy(o_cldljn, cldl*JrNt)
     749       IF (vars_defined)  zx_tmp_fi2d=cldl*JrNt
     750       CALL histwrite_phy(o_cldljn, zx_tmp_fi2d)
     751       !CALL histwrite_phy(o_cldmjn, cldm*JrNt)
     752       IF (vars_defined)  zx_tmp_fi2d=cldm*JrNt
     753       CALL histwrite_phy(o_cldmjn, zx_tmp_fi2d)
     754       !CALL histwrite_phy(o_cldhjn, cldh*JrNt)
     755       IF (vars_defined)  zx_tmp_fi2d=cldh*JrNt
     756       CALL histwrite_phy(o_cldhjn, zx_tmp_fi2d)
     757       !CALL histwrite_phy(o_cldtjn, cldt*JrNt)
     758       IF (vars_defined)  zx_tmp_fi2d=cldt*JrNt
     759       CALL histwrite_phy(o_cldtjn, zx_tmp_fi2d)
     760
    741761       CALL histwrite_phy(o_cldq, cldq)
    742762       IF (vars_defined)       zx_tmp_fi2d(1:klon) = flwp(1:klon)
     
    932952       IF (type_ocean=='slab ') THEN
    933953          CALL histwrite_phy(o_slab_qflux, slab_wfbils)
    934           CALL histwrite_phy(o_slab_bils, slab_bils)
     954          !CALL histwrite_phy(o_slab_bils, slab_bils)
    935955          IF (nslay.EQ.1) THEN
    936956              zx_tmp_fi2d(:)=tslab(:,1)
     
    967987          ENDDO
    968988       ENDIF
    969        CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
     989       !CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
    970990
    971991       IF (vars_defined) THEN
     
    974994          ENDDO
    975995       ENDIF
    976        CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
     996       !CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
    977997
    978998       CALL histwrite_phy(o_qsat2m, qsat2m)
     
    9961016          CALL histwrite_phy(o_od550aer, od550aer)
    9971017          CALL histwrite_phy(o_od865aer, od865aer)
    998           CALL histwrite_phy(o_absvisaer, absvisaer)
     1018          CALL histwrite_phy(o_abs550aer, abs550aer)
    9991019          CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
    10001020          CALL histwrite_phy(o_sconcso4, sconcso4)
     
    11361156       CALL histwrite_phy(o_rnebjn, zx_tmp_fi3d)
    11371157       CALL histwrite_phy(o_rhum, zx_rh)
    1138        CALL histwrite_phy(o_ozone, &
    1139             wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
     1158       !CALL histwrite_phy(o_ozone, &
     1159       !     wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
     1160       IF (vars_defined) zx_tmp_fi3d = wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd
     1161       CALL histwrite_phy(o_ozone, zx_tmp_fi3d)
    11401162
    11411163       IF (read_climoz == 2) THEN
    1142           CALL histwrite_phy(o_ozone_light, &
    1143                wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
    1144        ENDIF
    1145 
     1164         !CALL histwrite_phy(o_ozone_light, &
     1165         !     wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
     1166         IF (vars_defined) zx_tmp_fi3d = wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd
     1167         CALL histwrite_phy(o_ozone_light, zx_tmp_fi3d)
     1168       ENDIF
     1169
     1170       !AS: dans phys_output_write il y a en plus : CALL histwrite_phy(o_duphy, d_u)
    11461171       CALL histwrite_phy(o_dtphy, d_t)
    11471172       CALL histwrite_phy(o_dqphy,  d_qx(:,:,ivap))
     
    15851610#endif
    15861611!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1587         IF (nqtot.GE.nqo+1) THEN
    1588             DO iq=nqo+1,nqtot
    1589               IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    1590 
     1612       IF (nqtot.GE.nqo+1) THEN
     1613         !AS: type_trac = 'lmdz' par defaut dans libf/dyn3d/conf_gcm.F90
     1614         !Changé par inca, repr(obus), coag(ulation), co2i(nteractif), PAS par SPLA
     1615         !Cet "if" est donc inutile : IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     1616           DO iq=nqo+1,nqtot
    15911617             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
    15921618             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
     
    16121638             ENDIF
    16131639             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
    1614              ENDIF
    1615           ENDDO
     1640           ENDDO
     1641         !ENDIF
    16161642       ENDIF
    16171643
     
    16391665       ENDIF
    16401666
    1641     ENDDO
     1667    ENDDO ! iinit
    16421668
    16431669    IF (vars_defined) THEN
Note: See TracChangeset for help on using the changeset viewer.