Ignore:
Timestamp:
Jul 5, 2023, 12:03:42 PM (15 months ago)
Author:
acozic
Message:

Add of an output file containing mass flow when offline parameter is to "yes"
this file will be on horizontal grid with vertical level klev
When LMDZ is coupled to Inca, we don't call anymore the routine phystoken if offline=y

Anne Cozic

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4606 r4608  
    1919       ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ibs, ok_sync, &
    2020       ptconv, read_climoz, clevSTD, ptconvth, &
    21        d_u, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
     21       d_u, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc, t, u1, v1)
    2222
    2323    ! This subroutine does the actual writing of diagnostics that were
     
    3131    USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
    3232    USE vertical_layers_mod, ONLY : ap, bp, aps, bps
     33    USE phystokenc_mod, ONLY: offline
    3334    USE phys_output_ctrlout_mod, ONLY: o_phis, o_aire, is_ter, is_lic, is_oce, &
    3435         o_longitude, o_latitude, &
     
    360361         ep, epmax_diag, &  ! epmax_cape
    361362         p_tropopause, t_tropopause, z_tropopause, &
    362          zxfluxt,zxfluxq
    363 !FC
     363         zxfluxt,zxfluxq, &
     364! offline
     365         da, mp, phi, wght_cvfd
     366
    364367
    365368#ifdef CPP_StratAer
     
    458461    INTEGER :: flag_aerosol
    459462    LOGICAL :: ok_cdnc
     463    REAL, DIMENSION(klon,klev) :: t   ! output for phystoken - offline flux
     464    REAL, DIMENSION(klon) :: u1, v1   ! output for phystoken - offline flux
     465   
    460466    REAL, DIMENSION(3) :: freq_moyNMC
    461467
     
    482488#endif
    483489    REAL, PARAMETER :: un_jour=86400.
     490    CHARACTER(len=12) :: nvar   
    484491    INTEGER :: ISW, itr, ixt, it
    485492    CHARACTER*1 ch1
    486493    CHARACTER(LEN=maxlen) :: varname, dn
    487 
     494    REAL, DIMENSION(klon,klev) :: coefh_stok
     495   
     496   
    488497#ifdef CPP_StratAer
    489498    LOGICAL, PARAMETER :: debug_strataer=.FALSE.
     
    874883       CALL histwrite_phy(o_topl0, toplw0)
    875884
     885! offline
     886#ifdef CPP_XIOS
     887       IF (offline) THEN
     888
     889          coefh_stok(:,1)      = cdragh(:)
     890          coefh_stok(:,2:klev) = coefh(:,2:klev, is_ave)
     891         
     892          CALL histwrite_phy('upwd_stok', upwd)
     893          CALL histwrite_phy('t_stok', t)
     894          CALL histwrite_phy('fm_th_stok', fm_therm(:,1:klev))
     895          CALL histwrite_phy('en_th_stok', entr_therm)
     896          CALL histwrite_phy('da_stok',da )
     897          CALL histwrite_phy('mp_stok',mp )
     898          CALL histwrite_phy('dnwd_stok', dnwd)
     899          CALL histwrite_phy('wght_stok', wght_cvfd)
     900          CALL histwrite_phy('coefh_stok', coefh_stok)
     901          CALL histwrite_phy('yu1_stok', u1)
     902          CALL histwrite_phy('yv1_stok', v1)
     903
     904          DO k=1,klev
     905             IF (k<10) THEN
     906                WRITE(nvar,'(i1)') k
     907             ELSE IF (k<100) THEN
     908                WRITE(nvar,'(i2)') k
     909             ELSE
     910                WRITE(nvar,'(i3)') k
     911             END IF
     912             nvar='phi_lev'//trim(nvar)
     913             CALL histwrite_phy(nvar,phi(:,:,k))
     914          END DO
     915         
     916       ENDIF
     917#endif
     918
     919
     920
     921       
    876922       IF (vars_defined) THEN
    877923          zx_tmp_fi2d(:) = swup(:,klevp1)*swradcorr(:)
Note: See TracChangeset for help on using the changeset viewer.