Changeset 4118


Ignore:
Timestamp:
Mar 29, 2022, 12:43:14 PM (2 years ago)
Author:
evignon
Message:

correction variable with

Location:
LMDZ6/trunk/libf
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cloudth_mod.F90

    r4114 r4118  
    15501550      USE phys_output_var_mod, ONLY : cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv
    15511551      USE lscp_tools_mod, ONLY: CALC_QSAT_ECMWF, FALLICE_VELOCITY
    1552       USE phys_local_var_mod, ONLY : qlth, qith, qsith, with
     1552      USE phys_local_var_mod, ONLY : qlth, qith, qsith, wiceth
    15531553
    15541554      IMPLICIT NONE
     
    16891689      qlth(:,ind2)=0.
    16901690      qith(:,ind2)=0.
    1691       with(:,ind2)=0.
     1691      wiceth(:,ind2)=0.
    16921692      rneb(:,:)=0.
    16931693      qcloud(:)=0.
     
    19921992            ENDIF
    19931993
    1994             CALL ICE_MPC_BL_CLOUDS(ind1,ind2,klev,Ni,Ei,C_cap,d_top,iflag_topthermals,temp_mpc,pres_mpc,zqta(ind1,:),qsith(ind1,:),qlth(ind1,:),deltazlev_mpc,with(ind1,:),fraca_mpc,qith(ind1,:))
     1994            CALL ICE_MPC_BL_CLOUDS(ind1,ind2,klev,Ni,Ei,C_cap,d_top,iflag_topthermals,temp_mpc,pres_mpc,zqta(ind1,:), &
     1995                                   qsith(ind1,:),qlth(ind1,:),deltazlev_mpc,wiceth(ind1,:),fraca_mpc,qith(ind1,:))
    19951996
    19961997            ! qmax calculation
     
    22362237    ! Calcule ice fall velocity in thermals
    22372238
    2238     CALL FALLICE_VELOCITY(klon,qith(:,ind2),Tbefth(:),rhoth(:),paprs(:,ind2),falseklon(:),with(:,ind2))
     2239    CALL FALLICE_VELOCITY(klon,qith(:,ind2),Tbefth(:),rhoth(:),paprs(:,ind2),falseklon(:),wiceth(:,ind2))
    22392240
    22402241RETURN
     
    22442245
    22452246!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    2246 SUBROUTINE ICE_MPC_BL_CLOUDS(ind1,ind2,klev,Ni,Ei,C_cap,d_top,iflag_topthermals,temp,pres,qth,qsith,qlth,deltazlev,with,fraca,qith)
     2247SUBROUTINE ICE_MPC_BL_CLOUDS(ind1,ind2,klev,Ni,Ei,C_cap,d_top,iflag_topthermals,temp,pres,qth,qsith,qlth,deltazlev,vith,fraca,qith)
    22472248
    22482249! parameterization of ice for boundary
     
    23242325    REAL,  DIMENSION(klev), INTENT(IN) :: qlth       ! condensed liquid water in thermals, approximated value [kg/kg]
    23252326    REAL,  DIMENSION(klev), INTENT(IN) :: deltazlev  ! layer thickness [m]
    2326     REAL,  DIMENSION(klev), INTENT(IN) :: with       ! ice crystal fall velocity [m/s]
     2327    REAL,  DIMENSION(klev), INTENT(IN) :: vith       ! ice crystal fall velocity [m/s]
    23272328    REAL,  DIMENSION(klev+1), INTENT(IN) :: fraca      ! fraction of the mesh covered by thermals
    23282329    REAL,  DIMENSION(klev), INTENT(INOUT) :: qith       ! condensed ice water , thermals [kg/kg]
     
    24022403    fp1=0.
    24032404    IF (fraca(ind2p1) .GT. 0.) THEN
    2404     fp2=-qith(ind2p2)*rho(ind2p2)*with(ind2p2)*fraca(ind2p2)! flux defined positive upward
    2405     fp1=-qith(ind2p1)*rho(ind2p1)*with(ind2p1)*fraca(ind2p1)
     2405    fp2=-qith(ind2p2)*rho(ind2p2)*vith(ind2p2)*fraca(ind2p2)! flux defined positive upward
     2406    fp1=-qith(ind2p1)*rho(ind2p1)*vith(ind2p1)*fraca(ind2p1)
    24062407    ENDIF
    24072408
  • LMDZ6/trunk/libf/phylmd/phys_local_var_mod.F90

    r4114 r4118  
    438438      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: cldemi, cldfra, cldtau, fiwc, fl, re, flwc
    439439!$OMP THREADPRIVATE(cldemi, cldfra, cldtau, fiwc, fl, re, flwc)
    440       REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: qlth, qith, qsith, with
    441 !$OMP THREADPRIVATE(qlth, qith, qsith)
     440      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: qlth, qith, qsith, wiceth
     441!$OMP THREADPRIVATE(qlth, qith, qsith, wiceth)
    442442      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: ref_liq, ref_ice, theta, zphi
    443443!$OMP THREADPRIVATE(ref_liq, ref_ice, theta, zphi)
     
    778778      ALLOCATE(rain_lsc(klon))
    779779      ALLOCATE(rain_num(klon))
    780       ALLOCATE(qlth(klon,klev), qith(klon,klev), qsith(klon,klev), with(klon,klev))
     780      ALLOCATE(qlth(klon,klev), qith(klon,klev), qsith(klon,klev), wiceth(klon,klev))
    781781      !
    782782      ALLOCATE(sens_x(klon), sens_w(klon))
     
    10891089      DEALLOCATE(rain_lsc)
    10901090      DEALLOCATE(rain_num)
    1091       DEALLOCATE(qlth, qith, qsith, with)
     1091      DEALLOCATE(qlth, qith, qsith, wiceth)
    10921092!
    10931093      DEALLOCATE(sens_x, sens_w)
  • LMDZ6/trunk/libf/phylmdiso/phys_local_var_mod.F90

    r4072 r4118  
    559559      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: cldemi, cldfra, cldtau, fiwc, fl, re, flwc
    560560!$OMP THREADPRIVATE(cldemi, cldfra, cldtau, fiwc, fl, re, flwc)
    561       REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: qlth, qith, qsith
    562 !$OMP THREADPRIVATE(qlth, qith, qsith)
     561      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: qlth, qith, qsith, wiceth
     562!$OMP THREADPRIVATE(qlth, qith, qsith, wiceth)
    563563      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: ref_liq, ref_ice, theta, zphi
    564564!$OMP THREADPRIVATE(ref_liq, ref_ice, theta, zphi)
     
    943943      ALLOCATE(rain_lsc(klon))
    944944      ALLOCATE(rain_num(klon))
    945       ALLOCATE(qlth(klon,klev), qith(klon,klev), qsith(klon,klev))
     945      ALLOCATE(qlth(klon,klev), qith(klon,klev), qsith(klon,klev), wiceth(klon,klev))
    946946      !
    947947#ifdef ISO
     
    13251325      DEALLOCATE(rain_lsc)
    13261326      DEALLOCATE(rain_num)
    1327       DEALLOCATE(qlth, qith, qsith)
     1327      DEALLOCATE(qlth, qith, qsith, wiceth)
    13281328!
    13291329      DEALLOCATE(sens_x, sens_w)
Note: See TracChangeset for help on using the changeset viewer.