Ignore:
Timestamp:
Mar 17, 2015, 12:04:12 PM (9 years ago)
Author:
fhourdin
Message:

Changement du drapeau iflag_cldth en iflag_cld_th
et du défaut de iflag_cld_cv pour le choix entre schema
de nuages convectifs

lognormal = 0
bigaussien = 1

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

Legend:

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

    r2205 r2236  
    11SUBROUTINE calcratqs(klon,klev,prt_level,lunout,       &
    2            iflag_ratqs,iflag_con,iflag_cldth,pdtphys, &
     2           iflag_ratqs,iflag_con,iflag_cld_th,pdtphys, &
    33           ratqsbas,ratqshaut,tau_ratqs,fact_cldcon,   &
    44           ptconv,ptconvth,clwcon0th, rnebcon0th,      &
     
    1919! Input
    2020integer,intent(in) :: klon,klev,prt_level,lunout
    21 integer,intent(in) :: iflag_con,iflag_cldth,iflag_ratqs
     21integer,intent(in) :: iflag_con,iflag_cld_th,iflag_ratqs
    2222real,intent(in) :: pdtphys,ratqsbas,ratqshaut,fact_cldcon,tau_ratqs
    2323real, dimension(klon,klev+1),intent(in) :: paprs
     
    4343!   ----------------
    4444!   on ecrase le tableau ratqsc calcule par clouds_gno
    45       if (iflag_cldth.eq.1) then
     45      if (iflag_cld_th.eq.1) then
    4646         do k=1,klev
    4747         do i=1,klon
     
    5858!  par nversion de la fonction log normale
    5959!-----------------------------------------------------------------------
    60       else if (iflag_cldth.eq.4) then
     60      else if (iflag_cld_th.eq.4) then
    6161         ptconvth(:,:)=.false.
    6262         ratqsc(:,:)=0.
     
    136136!  -----------
    137137
    138       if (iflag_cldth.eq.1 .or.iflag_cldth.eq.2.or.iflag_cldth.eq.4) then
     138      if (iflag_cld_th.eq.1 .or.iflag_cld_th.eq.2.or.iflag_cld_th.eq.4) then
    139139
    140140! On ajoute une constante au ratqsc*2 pour tenir compte de
     
    165165!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    166166         ratqs(:,:)=max(ratqs(:,:),ratqss(:,:))
    167       else if (iflag_cldth<=6) then
     167      else if (iflag_cld_th<=6) then
    168168!   on ne prend que le ratqs stable pour fisrtilp
    169169         ratqs(:,:)=ratqss(:,:)
     
    174174             do i=1,klon
    175175                if (ratqsc(i,k).gt.1.e-10) then
    176                    ratqs(i,k)=ratqs(i,k)*zfratqs2+(iflag_cldth/100.)*ratqsc(i,k)*(1.-zfratqs2)
     176                   ratqs(i,k)=ratqs(i,k)*zfratqs2+(iflag_cld_th/100.)*ratqsc(i,k)*(1.-zfratqs2)
    177177                endif
    178178                ratqs(i,k)=min(ratqs(i,k)*zfratqs1+ratqss(i,k)*(1.-zfratqs1),0.5)
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r2227 r2236  
    1515       solarlong0,seuil_inversion, &
    1616       fact_cldcon, facttemps,ok_newmicro,iflag_radia,&
    17        iflag_cldth, &
     17       iflag_cld_th, &
    1818       iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    1919       ok_ade, ok_aie, ok_cdnc, aerosol_couple, &
     
    8181    REAL                 :: bl95_b0, bl95_b1
    8282    real                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut,tau_ratqs
    83     integer              :: iflag_cldth
     83    integer              :: iflag_cld_th
    8484    integer              :: iflag_ratqs
    8585
     
    113113    logical,save        :: ok_chlorophyll_omp ! albedo SB 
    114114    integer,SAVE        :: NSW_omp
    115     integer,SAVE        :: iflag_cldth_omp, ip_ebil_phy_omp
     115    integer,SAVE        :: iflag_cld_th_omp, ip_ebil_phy_omp
    116116    integer,SAVE        :: iflag_ratqs_omp
    117117
     
    900900
    901901    !
    902     !Config Key  = iflag_cldth
     902    !Config Key  = iflag_cld_th
    903903    !Config Desc = 
    904904    !Config Def  = 1
    905905    !Config Help =
    906906    !
    907     iflag_cldth_omp = 1
     907    iflag_cld_th_omp = 1
    908908! On lit deux fois avec l'ancien et le nouveau nom
    909909! pour assurer une retrocompatiblite.
    910910! A abandonner un jour
    911     call getin('iflag_cldcon',iflag_cldth_omp)
    912     call getin('iflag_cldth',iflag_cldth_omp)
    913 
    914     !
    915     !Config Key  = iflag_cld_cv
    916     !Config Desc =
    917     !Config Def  = 1
    918     !Config Help =
    919     !
    920     iflag_cld_cv_omp = 1
     911    call getin('iflag_cldcon',iflag_cld_th_omp)
     912    call getin('iflag_cld_th',iflag_cld_th_omp)
     913    iflag_cld_cv_omp = 0
    921914    call getin('iflag_cld_cv',iflag_cld_cv_omp)
    922915
     
    19821975    iflag_rrtm = iflag_rrtm_omp
    19831976    NSW = NSW_omp
    1984     iflag_cldth = iflag_cldth_omp
     1977    iflag_cld_th = iflag_cld_th_omp
    19851978    iflag_cld_cv = iflag_cld_cv_omp
    19861979    tau_cld_cv = tau_cld_cv_omp
     
    21372130    write(lunout,*)' reevap_ice = ', reevap_ice
    21382131    write(lunout,*)' iflag_pdf = ', iflag_pdf
    2139     write(lunout,*)' iflag_cldth = ', iflag_cldth
     2132    write(lunout,*)' iflag_cld_th = ', iflag_cld_th
    21402133    write(lunout,*)' iflag_cld_cv = ', iflag_cld_cv
    21412134    write(lunout,*)' tau_cld_cv = ', tau_cld_cv
  • LMDZ5/trunk/libf/phylmd/fisrtilp.F90

    r2223 r2236  
    88     frac_impa, frac_nucl, beta,                        &
    99     prfl, psfl, rhcl, zqta, fraca,                     &
    10      ztv, zpspsk, ztla, zthl, iflag_cldth,             &
     10     ztv, zpspsk, ztla, zthl, iflag_cld_th,             &
    1111     iflag_ice_thermo)
    1212
     
    8282  INTEGER ninter ! sous-intervals pour la precipitation
    8383  INTEGER ncoreczq 
    84   INTEGER iflag_cldth
     84  INTEGER iflag_cld_th
    8585  INTEGER iflag_ice_thermo
    8686  PARAMETER (ninter=5)
     
    545545           enddo
    546546
    547            if (iflag_cldth>=5) then
     547           if (iflag_cld_th>=5) then
    548548
    549549              call cloudth(klon,klev,k,ztv, &
     
    559559           endif
    560560
    561            if (iflag_cldth <= 4) then
     561           if (iflag_cld_th <= 4) then
    562562              lognormale = .true.
    563            elseif (iflag_cldth >= 6) then
     563           elseif (iflag_cld_th >= 6) then
    564564              ! lognormale en l'absence des thermiques
    565565              lognormale = fraca(:,k) < 1e-10
    566566           else
    567               ! Dans le cas iflag_cldth=5, on prend systématiquement la
     567              ! Dans le cas iflag_cld_th=5, on prend systématiquement la
    568568              ! bi-gaussienne
    569569              lognormale = .false.
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2235 r2236  
    639639  !$OMP THREADPRIVATE(fact_cldcon,facttemps)
    640640
    641   integer iflag_cldth
    642   save iflag_cldth
    643   !$OMP THREADPRIVATE(iflag_cldth)
     641  integer iflag_cld_th
     642  save iflag_cld_th
     643  !$OMP THREADPRIVATE(iflag_cld_th)
    644644  logical ptconv(klon,klev)
    645645  !IM cf. AM 081204 BEG
     
    919919          solarlong0,seuil_inversion, &
    920920          fact_cldcon, facttemps,ok_newmicro,iflag_radia, &
    921           iflag_cldth,iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
     921          iflag_cld_th,iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    922922          ok_ade, ok_aie, ok_cdnc, aerosol_couple,  &
    923923          flag_aerosol, flag_aerosol_strat, new_aod, &
     
    10271027     print*,'CYCLE_DIURNE', cycle_diurne
    10281028     !
    1029      IF (iflag_con.EQ.2.AND.iflag_cldth.GT.-1) THEN
    1030         abort_message = 'Tiedtke needs iflag_cldth=-2 or -1'
     1029     IF (iflag_con.EQ.2.AND.iflag_cld_th.GT.-1) THEN
     1030        abort_message = 'Tiedtke needs iflag_cld_th=-2 or -1'
    10311031        CALL abort_gcm (modname,abort_message,1)
    10321032     ENDIF
     
    11431143                ,alp_bl_prescr, ale_bl_prescr)
    11441144           ! 11/09/06 rajout initialisation ALE et ALP du wake et PBL(YU)
    1145            !        print*,'apres ini_wake iflag_cldth=', iflag_cldth
     1145           !        print*,'apres ini_wake iflag_cld_th=', iflag_cld_th
    11461146        endif
    11471147
     
    22982298     !   calcul des proprietes des nuages convectifs
    22992299     clwcon0(:,:)=fact_cldcon*clwcon0(:,:)
    2300      IF (iflag_cld_cv <= 1) THEN
     2300     IF (iflag_cld_cv == 0) THEN
    23012301     call clouds_gno &
    23022302          (klon,klev,q_seri,zqsat,clwcon0,ptconv,ratqsc,rnebcon0)
     
    25392539  END IF
    25402540
    2541   !      print*,'apres callwake iflag_cldth=', iflag_cldth
     2541  !      print*,'apres callwake iflag_cld_th=', iflag_cld_th
    25422542  !
    25432543  !===================================================================
     
    28602860  ! water distribution
    28612861  CALL  calcratqs(klon,klev,prt_level,lunout,        &
    2862        iflag_ratqs,iflag_con,iflag_cldth,pdtphys,  &
     2862       iflag_ratqs,iflag_con,iflag_cld_th,pdtphys,  &
    28632863       ratqsbas,ratqshaut,tau_ratqs,fact_cldcon,   &
    28642864       ptconv,ptconvth,clwcon0th, rnebcon0th,     &
     
    28822882       frac_impa, frac_nucl, beta_prec_fisrt, &
    28832883       prfl, psfl, rhcl,  &
    2884        zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cldth, &
     2884       zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cld_th, &
    28852885       iflag_ice_thermo)
    28862886  !
     
    29382938  !
    29392939  !IM cf FH
    2940   !     IF (iflag_cldth.eq.-1) THEN ! seulement pour Tiedtke
    2941   IF (iflag_cldth.le.-1) THEN ! seulement pour Tiedtke
     2940  !     IF (iflag_cld_th.eq.-1) THEN ! seulement pour Tiedtke
     2941  IF (iflag_cld_th.le.-1) THEN ! seulement pour Tiedtke
    29422942     snow_tiedtke=0.
    29432943     !     print*,'avant calcul de la pseudo precip '
    2944      !     print*,'iflag_cldth',iflag_cldth
    2945      if (iflag_cldth.eq.-1) then
     2944     !     print*,'iflag_cld_th',iflag_cld_th
     2945     if (iflag_cld_th.eq.-1) then
    29462946        rain_tiedtke=rain_con
    29472947     else
     
    29762976     ENDDO
    29772977
    2978   ELSE IF (iflag_cldth.ge.3) THEN
     2978  ELSE IF (iflag_cld_th.ge.3) THEN
    29792979     !  On prend pour les nuages convectifs le max du calcul de la
    29802980     !  convection et du calcul du pas de temps precedent diminue d'un facteur
     
    30663066     !   On prend la somme des fractions nuageuses et des contenus en eau
    30673067
    3068      if (iflag_cldth>=5) then
     3068     if (iflag_cld_th>=5) then
    30693069
    30703070        do k=1,klev
Note: See TracChangeset for help on using the changeset viewer.