Ignore:
Timestamp:
Sep 21, 2024, 1:46:45 PM (21 hours ago)
Author:
evignon
Message:

externalisation de la condensation avec lognormale dans lmdz_lscp_condensation
(par souci de coherence) apres verification de la convergence.

Location:
LMDZ6/trunk/libf/phylmd
Files:
2 edited

Legend:

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

    r5210 r5211  
    119119USE lmdz_lscp_ini, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG
    120120USE lmdz_lscp_ini, ONLY : ok_poprecip
    121 USE lmdz_lscp_ini, ONLY : ok_external_lognormal, ok_ice_supersat, ok_unadjusted_clouds, iflag_icefrac
     121USE lmdz_lscp_ini, ONLY : ok_ice_supersat, ok_unadjusted_clouds, iflag_icefrac
    122122
    123123IMPLICIT NONE
     
    968968
    969969
    970                   !--If .TRUE., calls an externalised version of the generalised
    971                   !--lognormal condensation scheme (Bony and Emanuel 2001)
    972                   !--Numerically, convergence is conserved with this option
    973                   !--The objective is to simplify LSCP
    974                   ELSEIF ( ok_external_lognormal ) THEN
    975                          
     970                  ELSE
     971                  !--generalised lognormal condensation scheme (Bony and Emanuel 2001)
     972
    976973                   CALL condensation_lognormal( &
    977974                       klon, Tbef, zq, zqs, gammasat, ratqs(:,k), &
    978975                       keepgoing, rneb(:,k), zqn, qvc)
    979976
    980 
    981                  ELSE !--Generalised lognormal (Bony and Emanuel 2001)
    982 
    983                   DO i=1,klon !todoan : check if loop in i is needed
    984 
    985                       IF (keepgoing(i)) THEN
    986 
    987                         zpdf_sig(i)=ratqs(i,k)*zq(i)
    988                         zpdf_k(i)=-sqrt(log(1.+(zpdf_sig(i)/zq(i))**2))
    989                         zpdf_delta(i)=log(zq(i)/(gammasat(i)*zqs(i)))
    990                         zpdf_a(i)=zpdf_delta(i)/(zpdf_k(i)*sqrt(2.))
    991                         zpdf_b(i)=zpdf_k(i)/(2.*sqrt(2.))
    992                         zpdf_e1(i)=zpdf_a(i)-zpdf_b(i)
    993                         zpdf_e1(i)=sign(min(ABS(zpdf_e1(i)),5.),zpdf_e1(i))
    994                         zpdf_e1(i)=1.-erf(zpdf_e1(i))
    995                         zpdf_e2(i)=zpdf_a(i)+zpdf_b(i)
    996                         zpdf_e2(i)=sign(min(ABS(zpdf_e2(i)),5.),zpdf_e2(i))
    997                         zpdf_e2(i)=1.-erf(zpdf_e2(i))
    998 
    999                           IF (zpdf_e1(i).LT.1.e-10) THEN
    1000                               rneb(i,k)=0.
    1001                               zqn(i)=zqs(i)
    1002                               !--AB grid-mean vapor in the cloud - we assume saturation adjustment
    1003                               qvc(i) = 0.
    1004                           ELSE
    1005                               rneb(i,k)=0.5*zpdf_e1(i)
    1006                               zqn(i)=zq(i)*zpdf_e2(i)/zpdf_e1(i)
    1007                               !--AB grid-mean vapor in the cloud - we assume saturation adjustment
    1008                               qvc(i) = rneb(i,k) * zqs(i)
    1009                           ENDIF
    1010 
    1011                       ENDIF ! keepgoing
    1012                   ENDDO ! loop on klon
    1013977
    1014978                  ENDIF ! .NOT. ok_ice_supersat
  • LMDZ6/trunk/libf/phylmd/lmdz_lscp_ini.F90

    r5210 r5211  
    144144
    145145  !--Parameters for condensation and ice supersaturation
    146   LOGICAL, SAVE, PROTECTED :: ok_external_lognormal=.FALSE.  ! if True, the lognormal condensation scheme is calculated in the lmdz_lscp_condensation routine
    147   !$OMP THREADPRIVATE(ok_external_lognormal)
    148146
    149147  LOGICAL, SAVE, PROTECTED :: ok_ice_supersat=.FALSE.        ! activates the condensation scheme that allows for ice supersaturation
     
    417415    CALL getin_p('snow_fallspeed_cld',snow_fallspeed_cld)
    418416    ! for condensation and ice supersaturation
    419     CALL getin_p('ok_external_lognormal',ok_external_lognormal)
    420417    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
    421418    CALL getin_p('ok_weibull_warm_clouds',ok_weibull_warm_clouds)
     
    498495    WRITE(lunout,*) 'lscp_ini, snow_fallspeed_cld:', snow_fallspeed_cld
    499496    ! for condensation and ice supersaturation
    500     WRITE(lunout,*) 'lscp_ini, ok_external_lognormal:', ok_external_lognormal
    501497    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
    502498    WRITE(lunout,*) 'lscp_ini, ok_unadjusted_clouds:', ok_unadjusted_clouds
     
    541537
    542538
    543     !--Check flags for condensation and ice supersaturation
    544     IF ( ok_external_lognormal .AND. ok_ice_supersat ) THEN
    545       abort_message = 'in lscp, ok_external_lognormal=y is incompatible with ok_ice_supersat=y'
    546       CALL abort_physic (modname,abort_message,1)
    547     ENDIF
    548 
    549539    IF ( ok_weibull_warm_clouds .AND. .NOT. ok_ice_supersat ) THEN
    550540      abort_message = 'in lscp, ok_weibull_warm_clouds=y needs ok_ice_supersat=y'
Note: See TracChangeset for help on using the changeset viewer.