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/cv3p1_closure.f90

    r5346 r5491  
    44SUBROUTINE cv3p1_closure(nloc, ncum, nd, icb, inb, pbase, plcl, p, ph, tv, &
    55    tvp, buoy, supmax, ok_inhib, ale, alp, omega,sig, w0, ptop2, cape, cin, m, &
    6     iflag, coef, plim1, plim2, asupmax, supmax0, asupmaxmin, cbmf, plfc, &
    7     wbeff)
     6    iflag, coef, coeftrue, plim1, plim2, asupmax, supmax0, asupmaxmin, &
     7    cbmf, plfc, wbeff)
    88
    99
     
    4848  REAL, DIMENSION (nloc), INTENT (OUT)               :: cape, cin
    4949  REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: m
     50  REAL, DIMENSION (nloc), INTENT (OUT)               :: coef, coeftrue
    5051  REAL, DIMENSION (nloc), INTENT (OUT)               :: plim1, plim2
    5152  REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: asupmax
     
    7475  REAL cbmflim(nloc), cbmf1(nloc), cbmfmax(nloc)
    7576  REAL cbmflast(nloc)
    76   REAL coef(nloc)
    7777  REAL xp(nloc), xq(nloc), xr(nloc), discr(nloc), b3(nloc), b4(nloc)
    7878  REAL theta(nloc), bb(nloc)
     
    598598  DO il = 1, ncum
    599599    coef(il) = (cbmf(il)+1.E-10)/(cbmflim(il)+1.E-10)
     600    coeftrue(il) = coef(il)
    600601  END DO
    601602  IF (prt_level>=20) PRINT *, 'cv3p1_param apres coef_plantePLUS'
Note: See TracChangeset for help on using the changeset viewer.