Changeset 2481


Ignore:
Timestamp:
Mar 29, 2016, 3:39:55 PM (8 years ago)
Author:
fhourdin
Message:

Introduction d'une dependance epmax=f(Cape) sur proposition de Camille Risi

Location:
LMDZ5/trunk/libf/phylmd
Files:
12 edited

Legend:

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

    r2346 r2481  
    1616                  evap, ep, epmlmMm, eplaMm, &                       ! RomP
    1717                  wdtrainA, wdtrainM, wght, qtc, sigt, &
    18                   tau_cld_cv, coefw_cld_cv)                           ! RomP+RL, AJ
     18                  tau_cld_cv, coefw_cld_cv, &                           ! RomP+RL, AJ
    1919!RomP <<<
     20                  epmax_diag) ! epmax_cape
    2021! **************************************************************
    2122! *
     
    148149  REAL zx_t, zdelta, zx_qs, zcor
    149150  REAL tau_cld_cv, coefw_cld_cv
     151  REAL epmax_diag(klon) ! epmax_cape
    150152
    151153!   INTEGER iflag_mix
     
    388390                   da, phi, mp, phi2, d1a, dam, sij, clw, elij, &       !RomP
    389391                   evap, ep, epmlmMm, eplaMm, &                         !RomP
    390                    wdtrainA, wdtrainM)                                  !RomP
     392                   wdtrainA, wdtrainM, &                                !RomP
     393                   epmax_diag) ! epmax_cape
    391394!           print *, 'cv_driver ->'      !jyg
    392395
     
    425428                    clw, elij, evap, ep, epmlmMm, eplaMm, &             ! RomP+RL
    426429                    wdtrainA, wdtrainM, qtc, sigt, &
    427                     tau_cld_cv, coefw_cld_cv                         ! RomP,AJ
     430                    tau_cld_cv, coefw_cld_cv, &                         ! RomP,AJ
    428431!AC!+!RomP+jyg
     432                    epmax_diag) ! epmax_cape
    429433  END IF
    430434! ------------------------------------------------------------------
  • LMDZ5/trunk/libf/phylmd/conema3.h

    r2253 r2481  
    44!
    55      real epmax             ! 0.993
     6      real coef_epmax_cape             ! 0.993
    67!jyg<
    78      REAL  cvl_comp_threshold     ! 0.
     
    1314
    1415!jyg<
    15 !!      common/comconema1/epmax,ok_adj_ema,iflag_clw,sig1feed,sig2feed
     16!!      common/comconema1/epmax,coef_epmax_cape,ok_adj_ema,iflag_clw,sig1feed,sig2feed
    1617!!      common/comconema2/iflag_cvl_sigd
    17       common/comconema1/epmax, cvl_comp_threshold, cvl_sig2feed
     18      common/comconema1/epmax,coef_epmax_cape, cvl_comp_threshold, cvl_sig2feed
    1819      common/comconema2/iflag_cvl_sigd, iflag_clw, ok_adj_ema
    1920!>jyg
    2021
    21 !      common/comconema/epmax,ok_adj_ema,iflag_clw
     22!      common/comconema/epmax,coef_epmax_cape,ok_adj_ema,iflag_clw
    2223!$OMP THREADPRIVATE(/comconema1/)
    2324!$OMP THREADPRIVATE(/comconema2/)
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r2456 r2481  
    155155    LOGICAL,SAVE :: ok_4xCO2atm_omp
    156156    REAL,SAVE :: epmax_omp
     157    REAL,SAVE :: coef_epmax_cape_omp
    157158    LOGICAL,SAVE :: ok_adj_ema_omp
    158159    INTEGER,SAVE :: iflag_clw_omp
     
    812813    epmax_omp = .993
    813814    call getin('epmax', epmax_omp)
     815
     816    coef_epmax_cape_omp = 0.0   
     817    call getin('coef_epmax_cape', coef_epmax_cape_omp)       
    814818    !
    815819    !Config Key  = ok_adj_ema
     
    19992003
    20002004    epmax = epmax_omp
     2005    coef_epmax_cape = coef_epmax_cape_omp
    20012006    ok_adj_ema = ok_adj_ema_omp
    20022007    iflag_clw = iflag_clw_omp
     
    23032308    write(lunout,*)'iflag_bergeron=',iflag_bergeron
    23042309    write(lunout,*)' epmax = ', epmax
     2310    write(lunout,*)' coef_epmax_cape = ', coef_epmax_cape
    23052311    write(lunout,*)' ok_adj_ema = ', ok_adj_ema
    23062312    write(lunout,*)' iflag_clw = ', iflag_clw
  • LMDZ5/trunk/libf/phylmd/cv30_routines.F90

    r2311 r2481  
    839839    q, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, tvp, clw, hp, &
    840840    ep, sigp, buoy)
     841    ! epmax_cape: ajout arguments
    841842  IMPLICIT NONE
    842843
     
    12421243  REAL dtmin(nloc, nd), sigold(nloc, nd)
    12431244
    1244 
    12451245  ! -------------------------------------------------------
    12461246  ! -- Initialization
     
    13481348
    13491349  ! the interval on which cape is computed starts at pbase :
    1350 
    13511350  DO k = 1, nl
    13521351    DO i = 1, ncum
     
    31463145    vprecip, evap, ep, sig, w0, ft, fq, fu, fv, ftra, inb, ma, upwd, dnwd, &
    31473146    dnwd0, qcondc, wd, cape, da, phi, mp, phi2, d1a, dam, sij, elij, clw, &
    3148     epmlmmm, eplamm, wdtraina, wdtrainm, iflag1, precip1, vprecip1, evap1, &
     3147    epmlmmm, eplamm, wdtraina, wdtrainm,epmax_diag, iflag1, precip1, vprecip1, evap1, &
    31493148    ep1, sig1, w01, ft1, fq1, fu1, fv1, ftra1, inb1, ma1, upwd1, dnwd1, &
    31503149    dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1, &
    3151     elij1, clw1, epmlmmm1, eplamm1, wdtraina1, wdtrainm1)
     3150    elij1, clw1, epmlmmm1, eplamm1, wdtraina1, wdtrainm1,epmax_diag1) ! epmax_cape
    31523151  IMPLICIT NONE
    31533152
     
    31703169  REAL wd(nloc), cape(nloc)
    31713170  REAL da(nloc, nd), phi(nloc, nd, nd), mp(nloc, nd)
     3171  REAL epmax_diag(nloc) ! epmax_cape
    31723172  ! RomP >>>
    31733173  REAL phi2(nloc, nd, nd)
     
    31933193  REAL wd1(nloc), cape1(nloc)
    31943194  REAL da1(nloc, nd), phi1(nloc, nd, nd), mp1(nloc, nd)
     3195  REAL epmax_diag1(len) ! epmax_cape
    31953196  ! RomP >>>
    31963197  REAL phi21(len, nd, nd)
     
    32113212    inb1(idcum(i)) = inb(i)
    32123213    cape1(idcum(i)) = cape(i)
     3214    epmax_diag1(idcum(i))=epmax_diag(i) ! epmax_cape
    32133215  END DO
    32143216
     
    32693271END SUBROUTINE cv30_uncompress
    32703272
     3273        subroutine cv30_epmax_fn_cape(nloc,ncum,nd &
     3274                ,cape,ep,hp,icb,inb,clw,nk,t,h,lv &
     3275                ,epmax_diag)
     3276        implicit none
     3277
     3278        ! On fait varier epmax en fn de la cape
     3279        ! Il faut donc recalculer ep, et hp qui a déjà été calculé et
     3280        ! qui en dépend
     3281        ! Toutes les autres variables fn de ep sont calculées plus bas.
     3282
     3283#include "cvthermo.h"
     3284#include "cv30param.h"
     3285#include "conema3.h"
     3286
     3287! inputs:
     3288      integer ncum, nd, nloc
     3289      integer icb(nloc), inb(nloc)
     3290      real cape(nloc)
     3291      real clw(nloc,nd),lv(nloc,nd),t(nloc,nd),h(nloc,nd)
     3292      integer nk(nloc)
     3293! inouts:
     3294      real ep(nloc,nd)
     3295      real hp(nloc,nd)
     3296! outputs ou local
     3297      real epmax_diag(nloc)
     3298! locals
     3299      integer i,k   
     3300      real hp_bak(nloc,nd)
     3301
     3302        ! on recalcule ep et hp
     3303       
     3304        if (coef_epmax_cape.gt.1e-12) then
     3305        do i=1,ncum
     3306           epmax_diag(i)=epmax-coef_epmax_cape*sqrt(cape(i))
     3307           do k=1,nl
     3308                ep(i,k)=ep(i,k)/epmax*epmax_diag(i)
     3309                ep(i,k)=amax1(ep(i,k),0.0)
     3310                ep(i,k)=amin1(ep(i,k),epmax_diag(i))
     3311           enddo
     3312        enddo
     3313
     3314! On recalcule hp:
     3315      do k=1,nl
     3316        do i=1,ncum
     3317          hp_bak(i,k)=hp(i,k)
     3318        enddo
     3319      enddo
     3320      do k=1,nlp
     3321        do i=1,ncum
     3322          hp(i,k)=h(i,k)
     3323        enddo
     3324      enddo
     3325      do k=minorig+1,nl
     3326       do i=1,ncum
     3327        if((k.ge.icb(i)).and.(k.le.inb(i)))then
     3328          hp(i,k)=h(i,nk(i))+(lv(i,k)+(cpd-cpv)*t(i,k))*ep(i,k)*clw(i,k)
     3329        endif
     3330       enddo
     3331      enddo !do k=minorig+1,n
     3332!     write(*,*) 'cv30_routines 6218: hp(1,20)=',hp(1,20)
     3333      do i=1,ncum 
     3334       do k=1,nl
     3335        if (abs(hp_bak(i,k)-hp(i,k)).gt.0.01) then
     3336           write(*,*) 'i,k=',i,k
     3337           write(*,*) 'coef_epmax_cape=',coef_epmax_cape
     3338           write(*,*) 'epmax_diag(i)=',epmax_diag(i)
     3339           write(*,*) 'ep(i,k)=',ep(i,k)
     3340           write(*,*) 'hp(i,k)=',hp(i,k)
     3341           write(*,*) 'hp_bak(i,k)=',hp_bak(i,k)
     3342           write(*,*) 'h(i,k)=',h(i,k)
     3343           write(*,*) 'nk(i)=',nk(i)
     3344           write(*,*) 'h(i,nk(i))=',h(i,nk(i))
     3345           write(*,*) 'lv(i,k)=',lv(i,k)
     3346           write(*,*) 't(i,k)=',t(i,k)
     3347           write(*,*) 'clw(i,k)=',clw(i,k)
     3348           write(*,*) 'cpd,cpv=',cpd,cpv
     3349           stop
     3350        endif
     3351       enddo !do k=1,nl
     3352      enddo !do i=1,ncum 
     3353      endif !if (coef_epmax_cape.gt.1e-12) then
     3354
     3355      return
     3356      end subroutine cv30_epmax_fn_cape
     3357
     3358
  • LMDZ5/trunk/libf/phylmd/cv3_routines.F90

    r2474 r2481  
    41424142                          ft, fq, fu, fv, ftra, &
    41434143                          Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
     4144                          epmax_diag, & ! epmax_cape
    41444145                          iflag1, &
    41454146                          precip1, sig1, w01, &
    41464147                          ft1, fq1, fu1, fv1, ftra1, &
    4147                           Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1)
     4148                          Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, &
     4149                          epmax_diag1) ! epmax_cape
    41484150  IMPLICIT NONE
    41494151
     
    41624164  REAL qcondc(nloc, nd)
    41634165  REAL wd(nloc), cape(nloc)
     4166  REAL epmax_diag(nloc)
    41644167
    41654168!outputs:
     
    41734176  REAL qcondc1(nloc, nd)
    41744177  REAL wd1(nloc), cape1(nloc)
     4178  REAL epmax_diag1(len) ! epmax_cape
    41754179
    41764180!local variables:
     
    41824186    wd1(idcum(i)) = wd(i)
    41834187    cape1(idcum(i)) = cape(i)
     4188    epmax_diag1(idcum(i))=epmax_diag(i) ! epmax_cape
    41844189  END DO
    41854190
     
    42164221  RETURN
    42174222END SUBROUTINE cv3_uncompress
     4223
     4224
     4225        subroutine cv3_epmax_fn_cape(nloc,ncum,nd &
     4226                 , ep,hp,icb,inb,clw,nk,t,h,hnk,lv,lf,frac &
     4227                 , pbase, p, ph, tv, buoy, sig, w0,iflag &
     4228                 , epmax_diag)
     4229        implicit none
     4230
     4231        ! On fait varier epmax en fn de la cape
     4232        ! Il faut donc recalculer ep, et hp qui a déjà été calculé et
     4233        ! qui en dépend
     4234        ! Toutes les autres variables fn de ep sont calculées plus bas.
     4235
     4236  include "cvthermo.h"
     4237  include "cv3param.h" 
     4238  include "conema3.h"
     4239  include "cvflag.h"
     4240
     4241! inputs:
     4242      INTEGER, INTENT (IN)                               :: ncum, nd, nloc
     4243      INTEGER, DIMENSION (nloc), INTENT (IN)             :: icb, inb, nk
     4244      REAL, DIMENSION (nloc), INTENT (IN)                :: hnk,pbase
     4245      REAL, DIMENSION (nloc, nd), INTENT (IN)            :: t, lv, lf, tv, h
     4246      REAL, DIMENSION (nloc, nd), INTENT (IN)            :: clw, buoy,frac
     4247      REAL, DIMENSION (nloc, nd), INTENT (IN)            :: sig,w0
     4248      INTEGER, DIMENSION (nloc), INTENT (IN)             :: iflag(nloc)
     4249      REAL, DIMENSION (nloc, nd), INTENT (IN)            :: p
     4250      REAL, DIMENSION (nloc, nd+1), INTENT (IN)          :: ph
     4251! inouts:
     4252      REAL, DIMENSION (nloc, nd), INTENT (INOUT)         :: ep,hp 
     4253! outputs
     4254      REAL, DIMENSION (nloc), INTENT (OUT)           :: epmax_diag
     4255
     4256! local
     4257      integer i,k   
     4258!      real hp_bak(nloc,nd)
     4259!      real ep_bak(nloc,nd)
     4260      real m_loc(nloc,nd)
     4261      real sig_loc(nloc,nd)
     4262      real w0_loc(nloc,nd)
     4263      integer iflag_loc(nloc)
     4264      real cape(nloc)
     4265       
     4266        if (coef_epmax_cape.gt.1e-12) then
     4267
     4268        ! il faut calculer la cape: on fait un calcule simple car tant qu'on ne
     4269        ! connait pas ep, on ne connait pas les mélanges, ddfts etc... qui sont
     4270        ! necessaires au calcul de la cape dans la nouvelle physique
     4271       
     4272!        write(*,*) 'cv3_routines check 4303'
     4273        do i=1,ncum
     4274        do k=1,nd
     4275          sig_loc(i,k)=sig(i,k)
     4276          w0_loc(i,k)=w0(i,k)
     4277          iflag_loc(i)=iflag(i)
     4278!          ep_bak(i,k)=ep(i,k)
     4279        enddo ! do k=1,nd
     4280        enddo !do i=1,ncum
     4281
     4282!        write(*,*) 'cv3_routines check 4311'
     4283!        write(*,*) 'nl=',nl
     4284        CALL cv3_closure(nloc, ncum, nd, icb, inb, & ! na->nd
     4285          pbase, p, ph, tv, buoy, &
     4286          sig_loc, w0_loc, cape, m_loc,iflag_loc)
     4287
     4288!        write(*,*) 'cv3_routines check 4316'
     4289!        write(*,*) 'ep(1,:)=',ep(1,:)
     4290        do i=1,ncum
     4291           epmax_diag(i)=epmax-coef_epmax_cape*sqrt(cape(i))
     4292           epmax_diag(i)=amax1(epmax_diag(i),0.0)
     4293!           write(*,*) 'i,icb,inb,cape,epmax_diag=', &
     4294!                i,icb(i),inb(i),cape(i),epmax_diag(i)
     4295           do k=1,nl
     4296                ep(i,k)=ep(i,k)/epmax*epmax_diag(i)
     4297                ep(i,k)=amax1(ep(i,k),0.0)
     4298                ep(i,k)=amin1(ep(i,k),epmax_diag(i))
     4299           enddo
     4300        enddo
     4301 !       write(*,*) 'ep(1,:)=',ep(1,:)
     4302
     4303      !write(*,*) 'cv3_routines check 4326'
     4304! On recalcule hp:
     4305!      do k=1,nl
     4306!        do i=1,ncum
     4307!         hp_bak(i,k)=hp(i,k)
     4308!       enddo
     4309!      enddo
     4310      do k=1,nl
     4311        do i=1,ncum
     4312          hp(i,k)=h(i,k)
     4313        enddo
     4314      enddo
     4315
     4316  IF (cvflag_ice) THEN
     4317
     4318      do k=minorig+1,nl
     4319       do i=1,ncum
     4320        if((k.ge.icb(i)).and.(k.le.inb(i)))then
     4321          hp(i, k) = hnk(i) + (lv(i,k)+(cpd-cpv)*t(i,k)+frac(i,k)*lf(i,k))* &
     4322                              ep(i, k)*clw(i, k)
     4323        endif
     4324       enddo
     4325      enddo !do k=minorig+1,n
     4326  ELSE !IF (cvflag_ice) THEN
     4327
     4328      DO k = minorig + 1, nl
     4329       DO i = 1, ncum
     4330        IF ((k>=icb(i)) .AND. (k<=inb(i))) THEN
     4331          hp(i,k)=hnk(i)+(lv(i,k)+(cpd-cpv)*t(i,k))*ep(i,k)*clw(i,k)
     4332        endif
     4333       enddo
     4334      enddo !do k=minorig+1,n
     4335
     4336  ENDIF !IF (cvflag_ice) THEN     
     4337      !write(*,*) 'cv3_routines check 4345'
     4338!      do i=1,ncum 
     4339!       do k=1,nl
     4340!        if ((abs(hp_bak(i,k)-hp(i,k))/hp_bak(i,k).gt.1e-1).or. &
     4341!            ((abs(hp_bak(i,k)-hp(i,k))/hp_bak(i,k).gt.1e-4).and. &
     4342!            (ep(i,k)-ep_bak(i,k).lt.1e-4))) then
     4343!           write(*,*) 'i,k=',i,k
     4344!           write(*,*) 'coef_epmax_cape=',coef_epmax_cape
     4345!           write(*,*) 'epmax_diag(i)=',epmax_diag(i)
     4346!           write(*,*) 'ep(i,k)=',ep(i,k)
     4347!           write(*,*) 'ep_bak(i,k)=',ep_bak(i,k)
     4348!           write(*,*) 'hp(i,k)=',hp(i,k)
     4349!           write(*,*) 'hp_bak(i,k)=',hp_bak(i,k)
     4350!           write(*,*) 'h(i,k)=',h(i,k)
     4351!           write(*,*) 'nk(i)=',nk(i)
     4352!           write(*,*) 'h(i,nk(i))=',h(i,nk(i))
     4353!           write(*,*) 'lv(i,k)=',lv(i,k)
     4354!           write(*,*) 't(i,k)=',t(i,k)
     4355!           write(*,*) 'clw(i,k)=',clw(i,k)
     4356!           write(*,*) 'cpd,cpv=',cpd,cpv
     4357!           stop
     4358!        endif
     4359!       enddo !do k=1,nl
     4360!      enddo !do i=1,ncum 
     4361      endif !if (coef_epmax_cape.gt.1e-12) then
     4362      !write(*,*) 'cv3_routines check 4367'
     4363
     4364      return
     4365      end subroutine cv3_epmax_fn_cape
     4366
     4367
     4368
  • LMDZ5/trunk/libf/phylmd/cv3a_uncompress.F90

    r2393 r2481  
    1313                           wdtrainA, wdtrainM, &                                ! RomP
    1414                           qtc, sigt,          &
    15                          
     15                           epmax_diag, & ! epmax_cape
    1616                           iflag1, kbas1, ktop1, &
    1717                           precip1, cbmf1, plcl1, plfc1, wbeff1, sig1, w01, ptop21, &
     
    2626                           clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &        ! RomP
    2727                           wdtrainA1, wdtrainM1, &                              ! RomP
    28                            qtc1, sigt1)
     28                           qtc1, sigt1, &
     29                           epmax_diag1) ! epmax_cape
    2930
    3031  ! **************************************************************
     
    5253  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: sig, w0
    5354  REAL, DIMENSION (nloc), INTENT (IN)                :: ptop2
     55  REAL, DIMENSION (nloc), INTENT (IN)                :: epmax_diag
    5456  REAL, DIMENSION (nloc, nd), INTENT (IN)            :: ft, fq, fu, fv
    5557  REAL, DIMENSION (nloc, nd, ntra), INTENT (IN)      :: ftra
     
    8688  REAL, DIMENSION (len), INTENT (OUT)                :: wbeff1
    8789  REAL, DIMENSION (len, nd), INTENT (OUT)            :: sig1, w01
     90  REAL, DIMENSION (len), INTENT (OUT)                :: epmax_diag1 ! epmax_cape
    8891  REAL, DIMENSION (len), INTENT (OUT)                :: ptop21
    8992  REAL, DIMENSION (len, nd), INTENT (OUT)            :: ft1, fq1, fu1, fv1
     
    144147      supmax01(idcum(i)) = supmax0(i)
    145148      asupmaxmin1(idcum(i)) = asupmaxmin(i)
     149      epmax_diag1(idcum(i)) = epmax_diag(i)
    146150    END DO
    147151   
  • LMDZ5/trunk/libf/phylmd/cv_driver.F90

    r2346 r2481  
    88                                                                        ! RomP
    99    evap1, ep1, epmlmmm1, eplamm1, & ! RomP
    10     wdtraina1, wdtrainm1) ! RomP
     10    wdtraina1, wdtrainm1, & ! RomP
     11    epmax_diag1) ! epmax_cape
    1112
    1213  USE dimphy
     
    144145  REAL epmlmmm1(len, nd, nd), eplamm1(len, nd)
    145146  ! RomP <<<
     147  REAL epmax_diag1 (len) ! epmax_cape     
    146148
    147149  ! -------------------------------------------------------------------
     
    341343  REAL sigd(nloc)
    342344  ! RomP <<<
     345  REAL epmax_diag(nloc) ! epmax_cape
    343346
    344347  nent(:, :) = 0
     
    402405  wd1(:) = 0.0
    403406  cape1(:) = 0.0
     407  epmax_diag1(:) = 0.0 ! epmax_cape
     408
    404409
    405410  IF (iflag_con==30) THEN
     
    554559      CALL cv30_closure(nloc, ncum, nd, icb, inb & ! na->nd
    555560        , pbase, p, ph, tv, buoy, sig, w0, cape, m)
     561
     562      ! epmax_cape
     563      call cv30_epmax_fn_cape(nloc,ncum,nd &
     564                ,cape,ep,hp,icb,inb,clw,nk,t,h,lv &
     565                ,epmax_diag)
     566        ! on écrase ep et recalcule hp
    556567    END IF
    557568
     
    560571        cpn, iflag, cbmf)
    561572    END IF
     573   
    562574
    563575    ! -------------------------------------------------------------------
     
    643655        da, phi, mp, phi2, d1a, dam, sij & !RomP
    644656        , elij, clw, epmlmmm, eplamm & !RomP
    645         , wdtraina, wdtrainm &     !RomP
     657        , wdtraina, wdtrainm,epmax_diag &     !RomP
    646658        , iflag1, precip1, vprecip1, evap1, ep1, sig1, w01 & !RomP
    647659        , ft1, fq1, fu1, fv1, ftra1, inb1, ma1, upwd1, dnwd1, dnwd01, &
    648660        qcondc1, wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1 & !RomP
    649661        , elij1, clw1, epmlmmm1, eplamm1 & !RomP
    650         , wdtraina1, wdtrainm1) !RomP
     662        , wdtraina1, wdtrainm1,epmax_diag1) !RomP
    651663    END IF
    652664
  • LMDZ5/trunk/libf/phylmd/cva_driver.F90

    r2420 r2481  
    2727                      clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, &        ! RomP, RL
    2828                      wdtrainA1, wdtrainM1, qtc1, sigt1, tau_cld_cv, &
    29                       coefw_cld_cv)                                        ! RomP, AJ
     29                      coefw_cld_cv, &                                      ! RomP, AJ
     30                      epmax_diag1)  ! epmax_cape
    3031! **************************************************************
    3132! *
     
    259260  REAL, DIMENSION (len, nd), INTENT (OUT)            :: d1a1, dam1
    260261! RomP <<<
     262  REAL, DIMENSION (len ), INTENT (OUT)               :: epmax_diag1     
    261263
    262264! -------------------------------------------------------------------
     
    524526  REAL d1a(len, nd), dam(len, nd)
    525527! RomP <<<
     528  REAL epmax_diag(nloc) ! epmax_cape
    526529
    527530  LOGICAL, SAVE :: first = .TRUE.
     
    892895    END IF
    893896
     897    ! epmax_cape
     898    ! on recalcule ep et hp   
     899    call cv3_epmax_fn_cape(nloc,ncum,nd &
     900                , ep,hp,icb,inb,clw,nk,t,h,hnk,lv,lf,frac &
     901                , pbase, p, ph, tv, buoy, sig, w0,iflag &
     902                , epmax_diag)
     903
    894904! -------------------------------------------------------------------
    895905! --- MIXING(1)   (if iflag_mix .ge. 1)
     
    11281138                           clw, elij, evap, ep, epmlmMm, eplaMm, &       ! RomP
    11291139                           wdtrainA, wdtrainM, &                         ! RomP
    1130                            qtc, sigt, &
     1140                           qtc, sigt, epmax_diag, & ! epmax_cape
    11311141                           iflag1, kbas1, ktop1, &
    11321142                           precip1, cbmf1, plcl1, plfc1, wbeff1, sig1, w01, ptop21, &
     
    11411151                           clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP
    11421152                           wdtrainA1, wdtrainM1,                       & ! RomP
    1143                            qtc1, sigt1)
     1153                           qtc1, sigt1, epmax_diag1) ! epmax_cape
    11441154    END IF
    11451155
  • LMDZ5/trunk/libf/phylmd/phys_local_var_mod.F90

    r2385 r2481  
    342342      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: dnwd, dnwd0, upwd, omega
    343343!$OMP THREADPRIVATE(dnwd, dnwd0, upwd, omega)
     344      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: epmax_diag ! epmax_cape
     345!$OMP THREADPRIVATE(epmax_diag)
     346      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: ep ! epmax_cape
     347!$OMP THREADPRIVATE(ep)
    344348!      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: coefh, coefm, lambda_th
    345349      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: lambda_th
     
    560564!      ALLOCATE(upwd(klon, klev), omega(klon, klev), coefh(klon, klev))
    561565      ALLOCATE(upwd(klon, klev), omega(klon, klev))
     566      ALLOCATE(epmax_diag(klon)) ! epmax_cape
     567      ALLOCATE(ep(klon,klev)) ! epmax_cape
    562568!      ALLOCATE(coefm(klon, klev), lambda_th(klon, klev), cldemi(klon, klev))
    563569      ALLOCATE(lambda_th(klon, klev), cldemi(klon, klev))
     
    761767!      DEALLOCATE(upwd, omega, coefh)
    762768      DEALLOCATE(upwd, omega)
     769      DEALLOCATE(epmax_diag)
     770      DEALLOCATE(ep)
    763771!      DEALLOCATE(coefm, lambda_th, cldemi)
    764772      DEALLOCATE(lambda_th, cldemi)
  • LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r2390 r2481  
    982982  TYPE(ctrl_out), SAVE :: o_upwd = ctrl_out((/ 2, 10, 10, 10, 10, 10, 11, 11, 11 /), &
    983983    'upwd', 'saturated updraft', 'kg/m2/s', (/ ('', i=1, 9) /))
     984  TYPE(ctrl_out), SAVE :: o_epmax_diag = ctrl_out((/ 2, 10, 10, 10, 10, 10, 11, 11, 11 /), &
     985    'epmax', 'epmax en fn cape', 'su', (/ ('', i=1, 9) /))
     986  TYPE(ctrl_out), SAVE :: o_ep = ctrl_out((/ 2, 10, 10, 10, 10, 10, 11, 11, 11 /), &
     987    'ep', 'ep', 'su', (/ ('', i=1, 9) /))
    984988  TYPE(ctrl_out), SAVE :: o_dtphy = ctrl_out((/ 2, 10, 10, 10, 10, 10, 11, 11, 11 /), &
    985989    'dtphy', 'Physics dT', 'K/s', (/ ('', i=1, 9) /))
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r2429 r2481  
    3737         o_psol, o_mass, o_qsurf, o_qsol, &
    3838         o_precip, o_ndayrain, o_plul, o_pluc, &
    39          o_snow, o_msnow, o_fsnow, o_evap, &
     39         o_snow, o_msnow, o_fsnow, o_evap, o_ep,o_epmax_diag, & ! epmax_cape
    4040         o_tops, o_tops0, o_topl, o_topl0, &
    4141         o_SWupTOA, o_SWupTOAclr, o_SWdnTOA, &
     
    6565         o_ue, o_ve, o_uq, o_vq, o_cape, o_pbase, &
    6666         o_ptop, o_fbase, o_plcl, o_plfc, &
    67          o_wbeff, o_cape_max, o_upwd, o_Ma, &
     67         o_wbeff, o_cape_max, o_upwd, o_ep,o_epmax_diag, o_Ma, &
    6868         o_dnwd, o_dnwd0, o_ftime_con, o_mc, &
    6969         o_prw, o_s_pblh, o_s_pblt, o_s_lcl, &
     
    249249         dv_gwd_rando, dv_gwd_front, &
    250250         east_gwstress, west_gwstress, &
    251          d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD
     251         d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD, &
     252         ep, epmax_diag ! epmax_cape
    252253
    253254    USE phys_output_var_mod, only: vars_defined, snow_o, zfra_o, bils_diss, &
     
    428429       CALL histwrite_phy(o_precip, zx_tmp_fi2d)
    429430       CALL histwrite_phy(o_ndayrain, nday_rain)
     431
     432       ! epmax_cape:
     433       CALL histwrite_phy(o_epmax_diag, epmax_diag)
     434       CALL histwrite_phy(o_ep, ep)
    430435
    431436       IF (vars_defined) THEN
  • LMDZ5/trunk/libf/phylmd/physiq_mod.F90

    r2477 r2481  
    266266    real phi2(klon,klev,klev)
    267267    real d1a(klon,klev),dam(klon,klev)
    268     real ev(klon,klev),ep(klon,klev)
     268    real ev(klon,klev)
    269269    real clw(klon,klev),elij(klon,klev,klev)
    270270    real epmlmMm(klon,klev,klev),eplaMm(klon,klev)
     
    24802480               ev, ep,epmlmMm,eplaMm, &
    24812481               wdtrainA,wdtrainM,wght_cvfd,qtc_cv,sigt_cv, &
    2482                tau_cld_cv,coefw_cld_cv)
     2482               tau_cld_cv,coefw_cld_cv,epmax_diag)
    24832483          ! RomP <<<
    24842484
Note: See TracChangeset for help on using the changeset viewer.