Ignore:
Timestamp:
Jan 19, 2025, 6:48:10 PM (5 hours ago)
Author:
jyg
Message:

New outputs :

+ coef_clos = [conv mass flux given by Alp closure]/[conv mass flux given by Emanuel scheme closure]
+ coef_clos_eff = effective coefficient used in the convective scheme.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cv3a_uncompress.f90

    r5346 r5491  
     1! $Id$
     2
    13SUBROUTINE cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, compress, &
    24                           iflag, kbas, ktop, &
     
    911                           plim1, plim2, asupmax, supmax0, &
    1012                           asupmaxmin, &
     13                           coef_clos, coef_clos_eff, &
    1114                           da, phi, mp, phi2, d1a, dam, sigij, &                ! RomP+AC+jyg
    1215                           qta, clw, elij, evap, ep, epmlmMm, eplaMm, &         ! RomP+jyg
     
    2326                           plim11, plim21, asupmax1, supmax01, &
    2427                           asupmaxmin1, &
     28                           coef_clos1, coef_clos_eff1, &
    2529                           da1, phi1, mp1, phi21, d1a1, dam1, sigij1, &         ! RomP+AC+jyg
    2630                           qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &  ! RomP+jyg
     
    6872  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: asupmax
    6973  REAL, DIMENSION (nloc), INTENT (IN)                :: supmax0, asupmaxmin
     74  REAL, DIMENSION (nloc), INTENT (IN)                :: coef_clos, coef_clos_eff
    7075
    7176  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: da
     
    105110  REAL, DIMENSION (len, nd), INTENT (OUT)            :: asupmax1
    106111  REAL, DIMENSION (len), INTENT (OUT)                :: supmax01, asupmaxmin1
     112  REAL, DIMENSION (len), INTENT (OUT)                :: coef_clos1, coef_clos_eff1
    107113                                                   
    108114  REAL, DIMENSION (len, nd), INTENT (OUT)            :: da1
     
    149155      supmax01(idcum(i)) = supmax0(i)
    150156      asupmaxmin1(idcum(i)) = asupmaxmin(i)
     157      coef_clos1(idcum(i)) = coef_clos(i)
     158      coef_clos_eff1(idcum(i)) = coef_clos_eff(i)
    151159      epmax_diag1(idcum(i)) = epmax_diag(i)
    152160    END DO
     
    282290      supmax01(:) = supmax0(:)
    283291      asupmaxmin1(:) = asupmaxmin(:)
     292      coef_clos1(:) = coef_clos(:)
     293      coef_clos_eff1(:) = coef_clos_eff(:)
    284294!
    285295      sig1(:, 1:nl) = sig(:, 1:nl)
Note: See TracChangeset for help on using the changeset viewer.