Changeset 5618 for LMDZ6/branches/contrails/libf/phylmd/cv3a_uncompress.f90
- Timestamp:
- Apr 15, 2025, 11:56:45 AM (2 months ago)
- Location:
- LMDZ6/branches/contrails
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/contrails
- Property svn:mergeinfo changed
/LMDZ6/trunk merged: 5451,5458,5460,5463,5468-5487,5490-5496,5499-5520,5524-5526,5528,5531,5544,5554-5557,5559-5562,5569-5572,5578,5582-5585,5597
- Property svn:mergeinfo changed
-
LMDZ6/branches/contrails/libf/phylmd/cv3a_uncompress.f90
r5346 r5618 1 ! $Id$ 2 1 3 SUBROUTINE cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, compress, & 2 4 iflag, kbas, ktop, & … … 9 11 plim1, plim2, asupmax, supmax0, & 10 12 asupmaxmin, & 13 coef_clos, coef_clos_eff, & 11 14 da, phi, mp, phi2, d1a, dam, sigij, & ! RomP+AC+jyg 12 15 qta, clw, elij, evap, ep, epmlmMm, eplaMm, & ! RomP+jyg … … 23 26 plim11, plim21, asupmax1, supmax01, & 24 27 asupmaxmin1, & 28 coef_clos1, coef_clos_eff1, & 25 29 da1, phi1, mp1, phi21, d1a1, dam1, sigij1, & ! RomP+AC+jyg 26 30 qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP+jyg … … 68 72 REAL, DIMENSION (nloc, nd), INTENT (IN) :: asupmax 69 73 REAL, DIMENSION (nloc), INTENT (IN) :: supmax0, asupmaxmin 74 REAL, DIMENSION (nloc), INTENT (IN) :: coef_clos, coef_clos_eff 70 75 71 76 REAL, DIMENSION (nloc, nd), INTENT (IN) :: da … … 105 110 REAL, DIMENSION (len, nd), INTENT (OUT) :: asupmax1 106 111 REAL, DIMENSION (len), INTENT (OUT) :: supmax01, asupmaxmin1 112 REAL, DIMENSION (len), INTENT (OUT) :: coef_clos1, coef_clos_eff1 107 113 108 114 REAL, DIMENSION (len, nd), INTENT (OUT) :: da1 … … 149 155 supmax01(idcum(i)) = supmax0(i) 150 156 asupmaxmin1(idcum(i)) = asupmaxmin(i) 157 coef_clos1(idcum(i)) = coef_clos(i) 158 coef_clos_eff1(idcum(i)) = coef_clos_eff(i) 151 159 epmax_diag1(idcum(i)) = epmax_diag(i) 152 160 END DO … … 282 290 supmax01(:) = supmax0(:) 283 291 asupmaxmin1(:) = asupmaxmin(:) 292 coef_clos1(:) = coef_clos(:) 293 coef_clos_eff1(:) = coef_clos_eff(:) 284 294 ! 285 295 sig1(:, 1:nl) = sig(:, 1:nl)
Note: See TracChangeset
for help on using the changeset viewer.