Changeset 5491 for LMDZ6/trunk/libf/phylmd/cv3p1_closure.f90
- Timestamp:
- Jan 19, 2025, 6:48:10 PM (5 hours ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/cv3p1_closure.f90
r5346 r5491 4 4 SUBROUTINE cv3p1_closure(nloc, ncum, nd, icb, inb, pbase, plcl, p, ph, tv, & 5 5 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) 8 8 9 9 … … 48 48 REAL, DIMENSION (nloc), INTENT (OUT) :: cape, cin 49 49 REAL, DIMENSION (nloc, nd), INTENT (OUT) :: m 50 REAL, DIMENSION (nloc), INTENT (OUT) :: coef, coeftrue 50 51 REAL, DIMENSION (nloc), INTENT (OUT) :: plim1, plim2 51 52 REAL, DIMENSION (nloc, nd), INTENT (OUT) :: asupmax … … 74 75 REAL cbmflim(nloc), cbmf1(nloc), cbmfmax(nloc) 75 76 REAL cbmflast(nloc) 76 REAL coef(nloc)77 77 REAL xp(nloc), xq(nloc), xr(nloc), discr(nloc), b3(nloc), b4(nloc) 78 78 REAL theta(nloc), bb(nloc) … … 598 598 DO il = 1, ncum 599 599 coef(il) = (cbmf(il)+1.E-10)/(cbmflim(il)+1.E-10) 600 coeftrue(il) = coef(il) 600 601 END DO 601 602 IF (prt_level>=20) PRINT *, 'cv3p1_param apres coef_plantePLUS'
Note: See TracChangeset
for help on using the changeset viewer.