Ignore:
Timestamp:
Nov 21, 2019, 4:43:45 PM (4 years ago)
Author:
lguez
Message:

Merge revisions 3427:3600 of trunk into branch Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/cva_driver.F90

    r3197 r3605  
    2525!!                      elij1,evap1,ep1,epmlmMm1,eplaMm1, &                ! RomP
    2626                      da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, & ! RomP, RL
    27                       clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &        ! RomP, RL
    28                       wdtrainA1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &
     27                      qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &  ! RomP, RL
     28                      wdtrainA1, wdtrainS1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &     !!jygprl
    2929                      coefw_cld_cv, &                                      ! RomP, AJ
    3030                      epmax_diag1)  ! epmax_cape
     
    124124!                                      of dimension ND, defined at same grid levels as T, Q, QS and P.
    125125
    126 ! wdtrainA1     Real           Output   precipitation detrained from adiabatic draught;
     126! wdtrainA1     Real           Output   precipitation ejected from adiabatic draught;
     127!                                         should be used in tracer transport (cvltr)
     128! wdtrainS1     Real           Output   precipitation detrained from shedding of adiabatic draught;
    127129!                                         used in tracer transport (cvltr)
    128130! wdtrainM1     Real           Output   precipitation detrained from mixed draughts;
     
    248250
    249251! RomP >>>
    250   REAL, DIMENSION (len, nd), INTENT (OUT)            :: wdtrainA1, wdtrainM1 ! precipitation sources (extensive)
     252  REAL, DIMENSION (len, nd), INTENT (OUT)            :: wdtrainA1, wdtrainS1, wdtrainM1 ! precipitation sources (extensive)
    251253  REAL, DIMENSION (len, nd), INTENT (OUT)            :: mp1  ! unsat. mass flux (staggered grid)
    252254  REAL, DIMENSION (len, nd), INTENT (OUT)            :: da1  ! detrained mass flux of adiab. asc. air (extensive)
     
    258260  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: sigij1 ! mass fraction of env. air in mixed draughts (intensive)
    259261  REAL, DIMENSION (len, nd, nd), INTENT (OUT)        :: elij1! cond. water per unit mass of mixed draughts (intensive)
     262  REAL, DIMENSION (len, nd), INTENT (OUT)            :: qta1 ! total water per unit mass of the adiab. asc. (intensive)
    260263  REAL, DIMENSION (len, nd), INTENT (OUT)            :: clw1 ! cond. water per unit mass of the adiab. asc. (intensive)
    261264!JYG,RL
     
    467470  REAL tv_wake(nloc, nd)
    468471  REAL clw(nloc, nd)
     472  REAL, DIMENSION(nloc, nd)    :: qta, qpreca                       !!jygprl
    469473  REAL dph(nloc, nd)
    470474  REAL pbase(nloc), buoybase(nloc), th(nloc, nd)
     
    477481  REAL cin(nloc)
    478482  REAL m(nloc, nd)
     483  REAL mm(nloc, nd)
    479484  REAL ment(nloc, nd, nd), sigij(nloc, nd, nd)
    480485  REAL qent(nloc, nd, nd)
     
    494499  REAL, DIMENSION(len,nd)     :: wt, water, evap
    495500  REAL, DIMENSION(len,nd)     :: ice, fondue, b
    496   REAL, DIMENSION(len,nd)     :: frac, faci
     501  REAL, DIMENSION(len,nd)     :: frac_a, frac_s, faci               !!jygprl
    497502  REAL ft(nloc, nd), fq(nloc, nd)
    498503  REAL ftd(nloc, nd), fqd(nloc, nd)
     
    523528 
    524529! RomP >>>
    525   REAL wdtrainA(nloc, nd), wdtrainM(nloc, nd)
     530  REAL wdtrainA(nloc, nd), wdtrainS(nloc, nd), wdtrainM(nloc, nd)   !!jygprl
    526531  REAL da(len, nd), phi(len, nd, nd)
    527532  REAL epmlmMm(nloc, nd, nd), eplaMm(nloc, nd)
     
    613618  asupmaxmin1(:) = 0.
    614619
     620  tvp(:, :) = 0. !ym missing init, need to have a look by developpers
     621  tv(:, :) = 0. !ym missing init, need to have a look by developpers
     622
    615623  DO il = 1, len
    616624    cin1(il) = -100000.
     
    633641  qtc1(:, :) = 0.
    634642  wdtrainA1(:, :) = 0.
     643  wdtrainS1(:, :) = 0.
    635644  wdtrainM1(:, :) = 0.
    636645  da1(:, :) = 0.
     
    643652  sigij1(:, :, :) = 0.
    644653  elij1(:, :, :) = 0.
     654  qta1(:,:) = 0.
    645655  clw1(:,:) = 0.
    646656  wghti1(:,:) = 0.
     
    903913                         p, ph, h, tv, lv, lf, pbase, buoybase, plcl, &
    904914                         inb, tp, tvp, clw, hp, ep, sigp, buoy, &
    905                          frac)
     915                         frac_a, frac_s, qpreca, qta)                        !!jygprl
    906916    END IF
    907917
     
    912922                        tnk, qnk, gznk, t, q, qs, gz, &
    913923                        p, dph, h, tv, lv, &
    914                         inb, inbis, tp, tvp, clw, hp, ep, sigp, frac)
     924                        inb, inbis, tp, tvp, clw, hp, ep, sigp, frac_s)
    915925    END IF
    916926
     
    920930             PRINT *, 'cva_driver -> cv3_epmax_cape'
    921931    call cv3_epmax_fn_cape(nloc,ncum,nd &
    922                 , ep,hp,icb,inb,clw,nk,t,h,hnk,lv,lf,frac &
     932                , ep,hp,icb,inb,clw,nk,t,h,hnk,lv,lf,frac_s &
    923933                , pbase, p, ph, tv, buoy, sig, w0,iflag &
    924934                , epmax_diag)
     
    938948             PRINT *, 'cva_driver -> cv3p_mixing'
    939949        CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, &           ! na->nd
    940                          ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, &
     950!!                         ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, &
     951                         ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qta, &      !!jygprl
    941952                         unk, vnk, hp, tv, tvp, ep, clw, sig, &
    942953                         ment, qent, hent, uent, vent, nent, &
     
    10181029             PRINT *, 'cva_driver -> cv3_mixing'
    10191030        CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, &             ! na->nd
    1020                         ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, &
     1031                        ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qnk, &
    10211032                        unk, vnk, hp, tv, tvp, ep, clw, m, sig, &
    10221033                        ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent)
    10231034        CALL zilch(hent, nloc*nd*nd)
    10241035      ELSE
    1025         CALL cv3_mixscale(nloc, ncum, nd, ment, m)
     1036!!jyg:  Essais absurde pour voir
     1037!!        mm(:,1) = 0.
     1038!!        DO  i = 2,nd
     1039!!          mm(:,i) = m(:,i)*(1.-qta(:,i-1))
     1040!!        ENDDO
     1041        mm(:,:) = m(:,:)
     1042        CALL cv3_mixscale(nloc, ncum, nd, ment, mm)
    10261043        IF (debut) THEN
    10271044          PRINT *, ' cv3_mixscale-> '
     
    10591076                     t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, &
    10601077                     th_wake, tv_wake, lv_wake, lf_wake, cpn_wake, &
    1061                      ep, sigp, clw, &
     1078                     ep, sigp, clw, frac_s, qpreca, frac_a, qta, &                    !!jygprl
    10621079                     m, ment, elij, delt, plcl, coef_clos, &
    10631080                     mp, qp, up, vp, trap, wt, water, evap, fondue, ice, &
    10641081                     faci, b, sigd, &
    1065                      wdtrainA, wdtrainM)                                       ! RomP
     1082!!                     wdtrainA, wdtrainM)                                       ! RomP
     1083                     wdtrainA, wdtrainS, wdtrainM)                               !!jygprl
    10661084!
    10671085      IF (prt_level >= 10) THEN
     
    10721090           evap(igout,k), fondue(igout,k)
    10731091        ENDDO
    1074         Print *, 'cva_driver after cv3_unsat: wdtrainA, wdtrainM '
     1092        Print *, 'cva_driver after cv3_unsat: wdtrainA, wdtrainS, wdtrainM '     !!jygprl
    10751093        DO k = 1,nd
    1076         write (6, '(i4,2(1x,e13.6))'), &
    1077            k, wdtrainA(igout,k), wdtrainM(igout,k)
     1094        write (6, '(i4,3(1x,e13.6))'), &
     1095           k, wdtrainA(igout,k), wdtrainS(igout,k), wdtrainM(igout,k)            !!jygprl
    10781096        ENDDO
    10791097      ENDIF
     
    11091127                     t, q, t_wake, q_wake, s_wake, u, v, tra, &
    11101128                     gz, p, ph, h, hp, lv, lf, cpn, th, th_wake, &
    1111                      ep, clw, m, tp, mp, qp, up, vp, trap, &
     1129                     ep, clw, qpreca, m, tp, mp, qp, up, vp, trap, &
    11121130                     wt, water, ice, evap, fondue, faci, b, sigd, &
    11131131                     ment, qent, hent, iflag_mix, uent, vent, &
     
    11181136!!                     tls, tps, &                            ! useless . jyg
    11191137                     qcondc, wd, &
    1120                      ftd, fqd, qnk, qtc, sigt, tau_cld_cv, coefw_cld_cv)
     1138!!                     ftd, fqd, qnk, qtc, sigt, tau_cld_cv, coefw_cld_cv)
     1139                     ftd, fqd, qta, qtc, sigt, tau_cld_cv, coefw_cld_cv)         !!jygprl
     1140!
     1141!         Test conseravtion de l'eau
    11211142!
    11221143      IF (debut) THEN
     
    11391160                     t, q, u, v, &
    11401161                     gz, p, ph, h, hp, lv, cpn, &
    1141                      ep, clw, frac, m, mp, qp, up, vp, &
     1162                     ep, clw, frac_s, m, mp, qp, up, vp, &
    11421163                     wt, water, evap, &
    11431164                     ment, qent, uent, vent, nent, elij, &
     
    11841205                           asupmaxmin, &
    11851206                           da, phi, mp, phi2, d1a, dam, sigij, &         ! RomP
    1186                            clw, elij, evap, ep, epmlmMm, eplaMm, &       ! RomP
    1187                            wdtrainA, wdtrainM, &                         ! RomP
     1207                           qta, clw, elij, evap, ep, epmlmMm, eplaMm, &  ! RomP
     1208                           wdtrainA, wdtrainS, wdtrainM, &                         ! RomP
    11881209                           qtc, sigt, epmax_diag, & ! epmax_cape
    11891210                           iflag1, kbas1, ktop1, &
     
    11961217                           Plim11, plim21, asupmax1, supmax01, &
    11971218                           asupmaxmin1, &
    1198                            da1, phi1, mp1, phi21, d1a1, dam1, sigij1,  & ! RomP
    1199                            clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP
    1200                            wdtrainA1, wdtrainM1,                       & ! RomP
     1219                           da1, phi1, mp1, phi21, d1a1, dam1, sigij1,  &       ! RomP
     1220                           qta1, clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP
     1221                           wdtrainA1, wdtrainS1, wdtrainM1,                  & ! RomP
    12011222                           qtc1, sigt1, epmax_diag1) ! epmax_cape
    12021223!   
Note: See TracChangeset for help on using the changeset viewer.