Changeset 4755


Ignore:
Timestamp:
Nov 22, 2023, 3:46:17 PM (6 months ago)
Author:
lebasn
Message:

Methox: Update comments to correct units + bugfix on output variable

Location:
LMDZ6/trunk/libf
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/StratAer/stratH2O_methox.F90

    r4626 r4755  
    44SUBROUTINE stratH2O_methox(debutphy,paprs,dq_ch4mmr)
    55!
    6 ! output: CH4VMR in mmr (mass mixing ratio/sec: kg H2O/kg air)
     6! output: CH4VMR in MMR/s (mass mixing ratio/s or kg H2O/kg air/s)
    77
    88  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
     
    2626  include "dimensions.h"
    2727 
    28 ! Variable input
     28! Input variables
    2929  REAL paprs(klon,klev+1)
    30   LOGICAL, INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
    31 ! Variable output
    32 ! tendance buffer pour appel de add_phys_tend
     30  LOGICAL, INTENT(IN) :: debutphy   ! flag for first physiq step
     31! Output variables
     32! tendency buffer used in add_phys_tend subroutine (in physiq_mod)
    3333  REAL, INTENT(INOUT), DIMENSION(klon,klev)  :: dq_ch4mmr
    3434 
    35 ! Variables locales
     35! Local variables
    3636  INTEGER n_lat   ! number of latitudes in the input data
    3737  INTEGER n_lon   ! number of longitudes in the input data
     
    4242!$OMP THREADPRIVATE(mth_pre)
    4343 
    44 ! Champs reconstitues
     44! Reconstitutes fields
    4545  REAL paprs_glo(klon_glo,klev+1)
    4646 
     
    5454! levels of input data
    5555 
    56 !stratospheric H2O source from CH4 oxidation
    57 ! fixed climatos
    58 ! H2O production in VMR/sec)
     56! Stratospheric H2O source from CH4 oxidation from fixed climatos
     57! (H2O production in VMR/sec)
    5958  REAL, ALLOCATABLE :: CH4RVMR_in(:, :, :, :)
    6059  REAL, ALLOCATABLE :: CH4RVMR_mth(:, :, :)
     
    122121        !---correct latitudinal order,convert input from volume mixing ratio to mass mixing ratio
    123122        DO j=1,n_lat
    124            ! convert VMR/sec in mmr (mass mixing ratio/sec: kg H2O/kg air)
     123           ! convert VMR/s in MMR/s (mass mixing ratio/s or kg H2O/kg air/s)
    125124           ! x2 because CH4->2*H2O
    126125           CH4RVMR_mth(:,j,:) = 2*CH4RVMR_in(:,n_lat+1-j,:,mth_cur)*mH2Omol/mAIRmol
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4737 r4755  
    22602260
    22612261       IF (ok_qch4) THEN
    2262           IF (vars_defined) zx_tmp_fi3d=d_q_ch4 / pdtphys
     2262          IF (vars_defined) zx_tmp_fi3d=d_q_ch4
    22632263          CALL histwrite_phy(o_dqch4, zx_tmp_fi3d)
    22642264       ENDIF
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4745 r4755  
    50255025    !DC Calcul de la tendance due au methane
    50265026    IF (ok_qch4) THEN
    5027 !      d_q_ch4: H2O source in ppmv/sec
     5027!      d_q_ch4: H2O source from CH4 in MMR/s (mass mixing ratio/s or kg H2O/kg air/s)
    50285028#ifdef CPP_StratAer
    50295029       CALL stratH2O_methox(debut,paprs,d_q_ch4)
    50305030#else
    5031 !      ecmwf routine METHOX
     5031!      ECMWF routine METHOX
    50325032       CALL METHOX(1,klon,klon,klev,q_seri,d_q_ch4,pplay)
    50335033#endif
    5034        ! ajout de la tendance d'humidite due au methane
     5034       ! add humidity tendency due to methane
    50355035       d_q_ch4_dtime(:,:) = d_q_ch4(:,:)*phys_tstep
    50365036       CALL add_phys_tend(du0, dv0, dt0, d_q_ch4_dtime, dql0, dqi0, dqbs0, paprs, &
    50375037            'q_ch4', abortphy,flag_inhib_tend,itap,0)
    5038        d_q_ch4(:,:) = d_q_ch4_dtime(:,:)/phys_tstep
     5038       d_q_ch4(:,:) = d_q_ch4_dtime(:,:)/phys_tstep ! update with H2O conserv done in add_phys_tend
    50395039    ENDIF
    50405040    !
     
    50505050       
    50515051       SELECT CASE(flag_emit)
    5052        CASE(1) ! emission volc H2O dans LMDZ
     5052       CASE(1) ! emission volc H2O in LMDZ
    50535053          DO ieru=1, nErupt
    50545054             IF (year_cur==year_emit_vol(ieru).AND.&
     
    50585058               
    50595059                IF(flag_verbose_strataer) print *,'IN physiq_mod: date=',year_cur,mth_cur,day_cur
    5060                 ! initialisation tendance q emission
     5060                ! initialisation of q tendency emission
    50615061                d_q_emiss(:,:)=0.
    50625062                ! daily injection mass emission - NL
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4745 r4755  
    61966196    !DC Calcul de la tendance due au methane
    61976197    IF (ok_qch4) THEN
    6198 !      d_q_ch4: H2O source in ppmv/sec
     6198!      d_q_ch4: H2O source from CH4 in MMR/s (mass mixing ratio/s or kg H2O/kg air/s)
    61996199#ifdef CPP_StratAer
    62006200       CALL stratH2O_methox(debut,paprs,d_q_ch4)
    62016201#else
    6202 !      ecmwf routine METHOX
     6202!      ECMWF routine METHOX
    62036203       CALL METHOX(1,klon,klon,klev,q_seri,d_q_ch4,pplay)
    62046204#endif
    6205        ! ajout de la tendance d'humidite due au methane
     6205       ! add humidity tendency due to methane
    62066206       d_q_ch4_dtime(:,:) = d_q_ch4(:,:)*phys_tstep
    62076207#ifdef ISO
     
    62146214#endif     
    62156215     &   )
    6216        d_q_ch4(:,:) = d_q_ch4_dtime(:,:)/phys_tstep
    6217 #ifdef ISO
    6218        d_xt_ch4(:,:,:) = d_xt_ch4_dtime(:,:,:)/phys_tstep
     6216       d_q_ch4(:,:) = d_q_ch4_dtime(:,:)/phys_tstep ! update with H2O conserv done in add_phys_tend
     6217#ifdef ISO
     6218       d_xt_ch4(:,:,:) = d_xt_ch4_dtime(:,:,:)/phys_tstep ! update with H2O conserv done in add_phys_tend
    62196219#endif
    62206220    ENDIF
Note: See TracChangeset for help on using the changeset viewer.