/[lmdze]/trunk/phylmd/cv_driver.f90
ViewVC logotype

Diff of /trunk/phylmd/cv_driver.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 331 by guez, Thu Jun 13 14:40:06 2019 UTC revision 332 by guez, Tue Aug 13 09:19:22 2019 UTC
# Line 142  contains Line 142  contains
142      ! Compressed fields:      ! Compressed fields:
143      integer, allocatable:: idcum(:), iflag(:) ! (ncum)      integer, allocatable:: idcum(:), iflag(:) ! (ncum)
144      integer, allocatable:: icb(:) ! (ncum)      integer, allocatable:: icb(:) ! (ncum)
145      integer nent(klon, klev)      integer, allocatable:: nent(:, :) ! (ncum, 2:nl - 1)
146      integer icbs(klon)      integer icbs(klon)
147    
148      integer, allocatable:: inb(:) ! (ncum)      integer, allocatable:: inb(:) ! (ncum)
# Line 242  contains Line 242  contains
242         allocate(idcum(ncum), plcl(ncum), inb(ncum))         allocate(idcum(ncum), plcl(ncum), inb(ncum))
243         allocate(b(ncum, nl - 1), evap(ncum, nl), icb(ncum), iflag(ncum))         allocate(b(ncum, nl - 1), evap(ncum, nl), icb(ncum), iflag(ncum))
244         allocate(th(ncum, nl), lv(ncum, nl), cpn(ncum, nl), mp(ncum, nl))         allocate(th(ncum, nl), lv(ncum, nl), cpn(ncum, nl), mp(ncum, nl))
245           allocate(nent(ncum, 2:nl - 1))
246         idcum = pack((/(i, i = 1, klon)/), iflag1 == 0)         idcum = pack((/(i, i = 1, klon)/), iflag1 == 0)
247         CALL cv30_compress(idcum, iflag1, icb1, icbs1, plcl1, tnk1, qnk1, &         CALL cv30_compress(idcum, iflag1, icb1, icbs1, plcl1, tnk1, qnk1, &
248              gznk1, pbase1, buoybase1, t1, q1, qs1, u1, v1, gz1, th1, h1, lv1, &              gznk1, pbase1, buoybase1, t1, q1, qs1, u1, v1, gz1, th1, h1, lv1, &
# Line 251  contains Line 252  contains
252         CALL cv30_undilute2(icb, icbs(:ncum), tnk, qnk, gznk, t, qs, gz, p, h, &         CALL cv30_undilute2(icb, icbs(:ncum), tnk, qnk, gznk, t, qs, gz, p, h, &
253              tv, lv, pbase(:ncum), buoybase(:ncum), plcl, inb, tp, tvp, &              tv, lv, pbase(:ncum), buoybase(:ncum), plcl, inb, tp, tvp, &
254              clw, hp, ep, buoy)              clw, hp, ep, buoy)
255         CALL cv30_closure(icb, inb, pbase, p, ph(:ncum, :), tv, buoy, &         CALL cv30_closure(icb, inb, pbase, p, ph(:ncum, :), tv, buoy, sig, w0, &
256              sig, w0, cape, m)              cape, m)
257         CALL cv30_mixing(icb, inb, t, q, qs, u, v, h, lv, &         CALL cv30_mixing(icb, inb, t, q, qs, u, v, h, lv, hp, ep, clw, m, sig, &
258              hp, ep, clw, m, sig, ment, qent, uent, vent, nent, sij, elij, &              ment, qent, uent, vent, nent, sij, elij, ments, qents)
             ments, qents)  
259         CALL cv30_unsat(icb, inb, t(:ncum, :nl), q(:ncum, :nl), &         CALL cv30_unsat(icb, inb, t(:ncum, :nl), q(:ncum, :nl), &
260              qs(:ncum, :nl), gz, u(:ncum, :nl), v(:ncum, :nl), p, &              qs(:ncum, :nl), gz, u(:ncum, :nl), v(:ncum, :nl), p, &
261              ph(:ncum, :), th(:ncum, :nl - 1), tv, lv, cpn, ep(:ncum, :), &              ph(:ncum, :), th(:ncum, :nl - 1), tv, lv, cpn, ep(:ncum, :), &

Legend:
Removed from v.331  
changed lines
  Added in v.332

  ViewVC Help
Powered by ViewVC 1.1.21