Ignore:
Timestamp:
Jun 17, 2022, 4:24:49 PM (2 years ago)
Author:
lguez
Message:

Sync latest trunk changes to branch LMDZ-ECRAD.

Location:
LMDZ6/branches/LMDZ-ECRAD
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-ECRAD

  • LMDZ6/branches/LMDZ-ECRAD/libf/phylmd/newmicro.F90

    r3281 r4171  
    11! $Id$
    22
    3 SUBROUTINE newmicro(flag_aerosol, ok_cdnc, bl95_b0, bl95_b1, paprs, pplay, t, pqlwp, pclc, &
     3SUBROUTINE newmicro(flag_aerosol, ok_cdnc, bl95_b0, bl95_b1, paprs, pplay, t, pqlwp, picefra, pclc, &
    44    pcltau, pclemi, pch, pcl, pcm, pct, pctlwp, xflwp, xfiwp, xflwc, xfiwc, &
    5     mass_solu_aero, mass_solu_aero_pi, pcldtaupi, re, fl, reliq, reice, &
     5    mass_solu_aero, mass_solu_aero_pi, pcldtaupi, latitude_deg,re, fl, reliq, reice, &
    66    reliq_pi, reice_pi)
    77
     
    99  USE phys_local_var_mod, ONLY: scdnc, cldncl, reffclwtop, lcc, reffclws, &
    1010      reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra,  &
    11       zfice, dNovrN
     11      zfice, dNovrN, ptconv
    1212  USE phys_state_var_mod, ONLY: rnebcon, clwcon
    1313  USE icefrac_lsc_mod ! computes ice fraction (JBM 3/14)
    1414  USE ioipsl_getin_p_mod, ONLY : getin_p
    1515  USE print_control_mod, ONLY: lunout
     16  USE lscp_tools_mod, only: icefrac_lscp
     17
    1618
    1719
     
    2931
    3032  ! t-------input-R-temperature
    31   ! pqlwp---input-R-eau liquide nuageuse dans l'atmosphere dans la partie
    32   ! nuageuse (kg/kg)
     33  ! pqlwp---input-R-eau liquide nuageuse dans l'atmosphere dans la maille (kg/kg)
     34  ! picefra--input-R-fraction de glace dans les nuages
    3335  ! pclc----input-R-couverture nuageuse pour le rayonnement (0 a 1)
    3436  ! mass_solu_aero-----input-R-total mass concentration for all soluble
     
    3840  ! bl95_b0-input-R-a PARAMETER, may be varied for tests (s-sea, l-land)
    3941  ! bl95_b1-input-R-a PARAMETER, may be varied for tests (    -"-      )
     42  ! latitude_deg-input latitude in degrees
    4043
    4144  ! re------output-R-Cloud droplet effective radius multiplied by fl [um]
     
    5861  include "radepsi.h"
    5962  include "radopt.h"
     63  include "clesphys.h"
    6064
    6165  ! choix de l'hypothese de recouvrement nuageuse via radopt.h (IM, 19.07.2016)
     
    8185  REAL t(klon, klev)
    8286  REAL pclc(klon, klev)
    83   REAL pqlwp(klon, klev)
     87  REAL pqlwp(klon, klev), picefra(klon,klev)
    8488  REAL pcltau(klon, klev)
    8589  REAL pclemi(klon, klev)
    8690  REAL pcldtaupi(klon, klev)
     91  REAL latitude_deg(klon)
    8792
    8893  REAL pct(klon)
     
    124129  REAL, PARAMETER :: t_glace_max_old = 273.13
    125130
    126   REAL rel, tc, rei
     131  REAL rel, tc, rei, iwc, dei, deimin, deimax
    127132  REAL k_ice0, k_ice, df
    128133  PARAMETER (k_ice0=0.005) ! units=m2/g
     
    148153  ! jq-end
    149154  ! IM cf. CR:parametres supplementaires
     155  REAL dzfice(klon,klev)
    150156  REAL zclear(klon)
    151157  REAL zcloud(klon)
     
    229235  ELSE ! of IF (iflag_t_glace.EQ.0)
    230236    DO k = 1, klev
    231         CALL icefrac_lsc(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:,k))
    232  
    233 
    234         ! JBM: icefrac_lsc is now contained icefrac_lsc_mod
     237
     238! JBM: icefrac_lsc is now contained icefrac_lsc_mod
    235239!       zfice(i, k) = icefrac_lsc(t(i,k), t_glace_min, &
    236240!                                 t_glace_max, exposant_glace)
    237       DO i = 1, klon
     241
     242      IF (ok_new_lscp) THEN
     243          CALL icefrac_lscp(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:,k),dzfice(:,k))
     244      ELSE
     245          CALL icefrac_lsc(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:,k))
     246      ENDIF
     247
     248      DO i = 1, klon
     249       
     250        IF ((.NOT. ptconv(i,k)) .AND. ok_new_lscp .AND. ok_icefra_lscp) THEN
     251        ! EV: take the ice fraction directly from the lscp code
     252        ! consistent only for non convective grid points
     253        ! critical for mixed phase clouds
     254            zfice(i,k)=picefra(i,k)
     255        ENDIF
     256
    238257        ! -layer calculation
    239258        rhodz(i, k) = (paprs(i,k)-paprs(i,k+1))/rg ! kg/m2
     
    321340            rhodz(i, k)
    322341          zfiwp_var = 1000.*zfice(i, k)*pqlwp(i, k)/pclc(i, k)*rhodz(i, k)
    323           tc = t(i, k) - 273.15
    324           rei = d_rei_dt*tc + rei_max
    325           IF (tc<=-81.4) rei = rei_min
     342          ! Calculation of ice cloud effective radius in micron
     343          IF (iflag_rei .EQ. 1) THEN
     344            ! when we account for precipitation in the radiation scheme,
     345            ! It is recommended to use the rei formula from Sun and Rikkus 1999 with a revision
     346            ! from Sun 2001 (as in the IFS model)
     347            iwc=zfice(i, k)*pqlwp(i, k)/pclc(i,k)*zrho(i,k)*1000. !in cloud ice water content in g/m3
     348            dei=(1.2351+0.0105*(t(i,k)-273.15))*(45.8966*(iwc**0.2214) + &
     349               & 0.7957*(iwc**0.2535)*(t(i,k)-83.15))
     350            !deimax=155.0
     351            !deimin=20.+40*cos(abs(latitude_deg(i))/180.*RPI)
     352            !Etienne: deimax and deimin controled by rei_max and rei_min in physiq.def
     353            deimax=rei_max*2.0
     354            deimin=2.0*rei_min+40*cos(abs(latitude_deg(i))/180.*RPI)
     355            dei=min(dei,deimax)
     356            dei=max(dei,deimin)
     357            rei=3.*sqrt(3.)/8.*dei
     358           ELSE
     359            ! Default
     360            ! for ice clouds: as a function of the ambiant temperature
     361            ! [formula used by Iacobellis and Somerville (2000), with an
     362            ! asymptotical value of 3.5 microns at T<-81.4 C added to be
     363            ! consistent with observations of Heymsfield et al. 1986]:
     364            ! 2011/05/24 : rei_min = 3.5 becomes a free PARAMETER as well as
     365            ! rei_max=61.29
     366            tc = t(i, k) - 273.15
     367            rei = d_rei_dt*tc + rei_max
     368            IF (tc<=-81.4) rei = rei_min
     369           ENDIF
    326370
    327371          ! -- cloud optical thickness :
     
    401445        rel = rad_chaud(i, k)
    402446
    403         ! for ice clouds: as a function of the ambiant temperature
    404         ! [formula used by Iacobellis and Somerville (2000), with an
    405         ! asymptotical value of 3.5 microns at T<-81.4 C added to be
    406         ! consistent with observations of Heymsfield et al. 1986]:
    407         ! 2011/05/24 : rei_min = 3.5 becomes a free PARAMETER as well as
    408         ! rei_max=61.29
    409 
    410         tc = t(i, k) - 273.15
    411         rei = d_rei_dt*tc + rei_max
    412         IF (tc<=-81.4) rei = rei_min
    413 
     447        ! Calculation of ice cloud effective radius in micron
     448
     449
     450        IF (iflag_rei .GT. 0) THEN
     451
     452            ! when we account for precipitation in the radiation scheme,
     453            ! we use the rei formula from Sun and Rikkus 1999 with a revision
     454            ! from Sun 2001 (as in the IFS model)
     455            iwc=zfice(i, k)*pqlwp(i, k)/pclc(i,k)*zrho(i,k)*1000. !in cloud ice water content in g/m3
     456            dei=(1.2351+0.0105*(t(i,k)-273.15))*(45.8966*(iwc**0.2214) + &
     457               &0.7957*(iwc**0.2535)*(t(i,k)-83.15))
     458            !deimax=155.0
     459            !deimin=20.+40*cos(abs(latitude_deg(i))/180.*RPI)
     460            !Etienne: deimax and deimin controled by rei_max and rei_min in physiq.def
     461            deimax=rei_max*2.0
     462            deimin=2.0*rei_min+40*cos(abs(latitude_deg(i))/180.*RPI)
     463            dei=min(dei,deimax)
     464            dei=max(dei,deimin)
     465            rei=3.*sqrt(3.)/8.*dei
     466       
     467        ELSE
     468            ! Default
     469            ! for ice clouds: as a function of the ambiant temperature
     470            ! [formula used by Iacobellis and Somerville (2000), with an
     471            ! asymptotical value of 3.5 microns at T<-81.4 C added to be
     472            ! consistent with observations of Heymsfield et al. 1986]:
     473            ! 2011/05/24 : rei_min = 3.5 becomes a free PARAMETER as well as
     474            ! rei_max=61.29
     475            tc = t(i, k) - 273.15
     476            rei = d_rei_dt*tc + rei_max
     477            IF (tc<=-81.4) rei = rei_min
     478        ENDIF
    414479        ! -- cloud optical thickness :
    415480        ! [for liquid clouds, traditional formula,
Note: See TracChangeset for help on using the changeset viewer.