Ignore:
Timestamp:
Jan 5, 2016, 4:37:49 PM (8 years ago)
Author:
crio
Message:

Nouvelle option d'epluchage de l'ascendance adiabatique dans le schema d'Emanuel: epluchage fonction de B/w2 au lieu de w. S'active avec iflag_mix_adiab=1 (valeur par defaut iflag_mix_adiab=0). Fonctionne avec iflag_mix=0 et iflag_mix=1.
Correction de bugs dans le schema de convection pour le calcul de inb, cape et buoy (sous le meme flag pour l'instant).
New option for the erosion of the adiabatic ascent in the Emanuel scheme: erosion function of B/w2 instead of w. Activated by iflag_mix_adiab=1 (standard value iflag_mix_adiab=0). Should work with iflag_mix=0 and iflag_mix=1.
Various bug corrections in the convection scheme for the computation of inb, cape, buoy (protected by the same flag for now).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cv3_routines.F90

    r2398 r2420  
    10871087SUBROUTINE cv3_undilute2(nloc, ncum, nd, icb, icbs, nk, &
    10881088                         tnk, qnk, gznk, hnk, t, q, qs, gz, &
    1089                          p, h, tv, lv, lf, pbase, buoybase, plcl, &
     1089                         p, ph, h, tv, lv, lf, pbase, buoybase, plcl, &
    10901090                         inb, tp, tvp, clw, hp, ep, sigp, buoy, frac)
    10911091  IMPLICIT NONE
     
    11131113  include "conema3.h"
    11141114  include "cvflag.h"
     1115  include "YOMCST2.h"
    11151116
    11161117!inputs:
     
    11191120  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: t, q, qs, gz
    11201121  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: p
     1122  REAL, DIMENSION (nloc, nd+1), INTENT (IN)          :: ph
    11211123  REAL, DIMENSION (nloc), INTENT (IN)                :: tnk, qnk, gznk
    11221124  REAL, DIMENSION (nloc), INTENT (IN)                :: hnk
     
    11441146  INTEGER iposit(nloc)
    11451147  REAL fracg
     1148  REAL deltap
    11461149
    11471150! =====================================================================
     
    14761479    END DO
    14771480  END DO
     1481
     1482!CR fix computation of inb
     1483!keep flag or modify in all cases?
     1484  IF (iflag_mix_adiab.eq.1) THEN
     1485  DO i = 1, ncum
     1486     cape(i)=0.
     1487     inb(i)=icb(i)+1
     1488  ENDDO
     1489 
     1490  DO k = 2, nl
     1491    DO i = 1, ncum
     1492       IF ((k>=iposit(i))) THEN
     1493       deltap = min(plcl(i), ph(i,k-1)) - min(plcl(i), ph(i,k))
     1494       cape(i) = cape(i) + rrd*buoy(i, k-1)*deltap/p(i, k-1)
     1495       IF (cape(i).gt.0.) THEN
     1496        inb(i) = max(inb(i), k)
     1497       END IF
     1498       ENDIF
     1499    ENDDO
     1500  ENDDO
     1501
     1502!  DO i = 1, ncum
     1503!     print*,"inb",inb(i)
     1504!  ENDDO
     1505
     1506  endif
    14781507
    14791508! -- end convect3
Note: See TracChangeset for help on using the changeset viewer.