Ignore:
Timestamp:
Jul 12, 2017, 4:20:24 PM (7 years ago)
Author:
jbmadeleine
Message:
  • Added a new output called rneblsvol which is the cloud fraction by volume

computed in the thermals (see cloudth_vert in cloudth_mod.F90)

  • Added an option called iflag_rain_incloud_vol that computes the conversion

of cloud water to rain using the cloud fraction by volume instead of the cloud
fraction by area, which is larger and otherwise erroneously reduces the in-cloud
water content; iflag_rain_incloud_vol can only be used for iflag_cloudth_vert>=3

File:
1 edited

Legend:

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

    r2911 r2945  
    587587       SUBROUTINE cloudth_v3(ngrid,klev,ind2,  &
    588588     &           ztv,po,zqta,fraca, &
    589      &           qcloud,ctot,zpspsk,paprs,ztla,zthl, &
     589     &           qcloud,ctot,ctot_vol,zpspsk,paprs,ztla,zthl, &
    590590     &           ratqs,zqs,t)
    591591
     
    624624      REAL zqsatenv(ngrid,klev)
    625625     
    626      
    627       REAL sigma1(ngrid,klev)
     626      REAL sigma1(ngrid,klev)                                                         
    628627      REAL sigma2(ngrid,klev)
    629628      REAL qlth(ngrid,klev)
    630629      REAL qlenv(ngrid,klev)
    631630      REAL qltot(ngrid,klev)
    632       REAL cth(ngrid,klev) 
     631      REAL cth(ngrid,klev)
    633632      REAL cenv(ngrid,klev)   
    634633      REAL ctot(ngrid,klev)
    635       REAL rneb(ngrid,klev)
     634      REAL cth_vol(ngrid,klev)
     635      REAL cenv_vol(ngrid,klev)
     636      REAL ctot_vol(ngrid,klev)
     637      REAL rneb(ngrid,klev)     
    636638      REAL t(ngrid,klev)
    637639      REAL qsatmmussig1,qsatmmussig2,sqrt2pi,sqrt2,sqrtpi,pi
     
    652654      CALL cloudth_vert_v3(ngrid,klev,ind2,  &
    653655     &           ztv,po,zqta,fraca, &
    654      &           qcloud,ctot,zpspsk,paprs,ztla,zthl, &
     656     &           qcloud,ctot,ctot_vol,zpspsk,paprs,ztla,zthl, &
    655657     &           ratqs,zqs,t)
    656658      RETURN
     
    672674      cenv(:,:)=0.
    673675      ctot(:,:)=0.
     676      cth_vol(:,:)=0.
     677      cenv_vol(:,:)=0.
     678      ctot_vol(:,:)=0.
    674679      qsatmmussig1=0.
    675680      qsatmmussig2=0.
     
    747752      cenv(ind1,ind2)=0.5*(1.+1.*erf(xenv))     !4.18 p 111, l.7 p115 & 4.20 p 119 thesis Arnaud Jam
    748753      ctot(ind1,ind2)=fraca(ind1,ind2)*cth(ind1,ind2)+(1.-1.*fraca(ind1,ind2))*cenv(ind1,ind2)
     754      ctot_vol(ind1,ind2)=ctot(ind1,ind2)
    749755
    750756      qlth(ind1,ind2)=sigma2s*((exp(-1.*xth**2)/sqrt2pi)+xth*sqrt2*cth(ind1,ind2))
     
    780786      xenv=senv/(sqrt2*sigma1s)
    781787      ctot(ind1,ind2)=0.5*(1.+1.*erf(xenv))
     788      ctot_vol(ind1,ind2)=ctot(ind1,ind2)
    782789      qltot(ind1,ind2)=sigma1s*((exp(-1.*xenv**2)/sqrt2pi)+xenv*sqrt2*cenv(ind1,ind2))
    783790
     
    801808     SUBROUTINE cloudth_vert_v3(ngrid,klev,ind2,  &
    802809     &           ztv,po,zqta,fraca, &
    803      &           qcloud,ctot,zpspsk,paprs,ztla,zthl, &
     810     &           qcloud,ctot,ctot_vol,zpspsk,paprs,ztla,zthl, &
    804811     &           ratqs,zqs,t)
    805812
     
    838845      REAL zqsatenv(ngrid,klev)
    839846     
    840      
     847   
     848
     849
    841850      REAL sigma1(ngrid,klev)                                                         
    842851      REAL sigma2(ngrid,klev)
     
    844853      REAL qlenv(ngrid,klev)
    845854      REAL qltot(ngrid,klev)
    846       REAL cth(ngrid,klev) 
     855      REAL cth(ngrid,klev)
    847856      REAL cenv(ngrid,klev)   
    848857      REAL ctot(ngrid,klev)
     858      REAL cth_vol(ngrid,klev)
     859      REAL cenv_vol(ngrid,klev)
     860      REAL ctot_vol(ngrid,klev)
    849861      REAL rneb(ngrid,klev)
    850862      REAL t(ngrid,klev)                                                                 
     
    854866      REAL sth,senv,sigma1s,sigma2s,xth,xenv,exp_xenv1,exp_xenv2,exp_xth1,exp_xth2
    855867      REAL xth1,xth2,xenv1,xenv2,deltasth, deltasenv
    856       REAL IntJ,IntI1,IntI2,IntI3,coeffqlenv,coeffqlth
     868      REAL IntJ,IntI1,IntI2,IntI3,IntJ_CF,IntI1_CF,IntI3_CF,coeffqlenv,coeffqlth
    857869      REAL Tbef,zdelta,qsatbef,zcor
    858870      REAL qlbef 
     
    883895      cenv(:,:)=0.
    884896      ctot(:,:)=0.
     897      cth_vol(:,:)=0.
     898      cenv_vol(:,:)=0.
     899      ctot_vol(:,:)=0.
    885900      qsatmmussig1=0.
    886901      qsatmmussig2=0.
     
    10321047      exp_xth2 = exp(-1.*xth2**2)
    10331048     
     1049      !CF_surfacique
    10341050      cth(ind1,ind2)=0.5*(1.-1.*erf(xth1))
    10351051      cenv(ind1,ind2)=0.5*(1.-1.*erf(xenv1))
    1036       ctot(ind1,ind2)=fraca(ind1,ind2)*cth(ind1,ind2)+(1.-1.*fraca(ind1,ind2))*cenv(ind1,ind2)
    1037 
    1038      
     1052      ctot(ind1,ind2)=fraca(ind1,ind2)*cth(ind1,ind2)+(1.-1.*fraca(ind1,ind2))*cenv(ind1,ind2)
     1053
     1054
     1055      !CF_volumique & eau condense
    10391056      !environnement
    10401057      IntJ=0.5*senv*(1-erf(xenv2))+(sigma1s/sqrt2pi)*exp_xenv2
     1058      IntJ_CF=0.5*(1.-1.*erf(xenv2))
    10411059      if (deltasenv .lt. 1.e-10) then
    10421060      qlenv(ind1,ind2)=IntJ
     1061      cenv_vol(ind1,ind2)=IntJ_CF
    10431062      else
    10441063      IntI1=(((senv+deltasenv)**2+(sigma1s)**2)/(8*deltasenv))*(erf(xenv2)-erf(xenv1))
    10451064      IntI2=(sigma1s**2/(4*deltasenv*sqrtpi))*(xenv1*exp_xenv1-xenv2*exp_xenv2)
    10461065      IntI3=((sqrt2*sigma1s*(senv+deltasenv))/(4*sqrtpi*deltasenv))*(exp_xenv1-exp_xenv2)
     1066      IntI1_CF=((senv+deltasenv)*(erf(xenv2)-erf(xenv1)))/(4*deltasenv)
     1067      IntI3_CF=(sqrt2*sigma1s*(exp_xenv1-exp_xenv2))/(4*sqrtpi*deltasenv)
    10471068      qlenv(ind1,ind2)=IntJ+IntI1+IntI2+IntI3
     1069      cenv_vol(ind1,ind2)=IntJ_CF+IntI1_CF+IntI3_CF
    10481070      endif
    1049 
    10501071
    10511072      !thermique
    10521073      IntJ=0.5*sth*(1-erf(xth2))+(sigma2s/sqrt2pi)*exp_xth2
    1053       if (deltasth .lt. 1.e-10) then ! Seuil a choisir !!!
     1074      IntJ_CF=0.5*(1.-1.*erf(xth2))
     1075      if (deltasth .lt. 1.e-10) then
    10541076      qlth(ind1,ind2)=IntJ
     1077      cth_vol(ind1,ind2)=IntJ_CF
    10551078      else
    10561079      IntI1=(((sth+deltasth)**2+(sigma2s)**2)/(8*deltasth))*(erf(xth2)-erf(xth1))
    10571080      IntI2=(sigma2s**2/(4*deltasth*sqrtpi))*(xth1*exp_xth1-xth2*exp_xth2)
    10581081      IntI3=((sqrt2*sigma2s*(sth+deltasth))/(4*sqrtpi*deltasth))*(exp_xth1-exp_xth2)
     1082      IntI1_CF=((sth+deltasth)*(erf(xth2)-erf(xth1)))/(4*deltasth)
     1083      IntI3_CF=(sqrt2*sigma2s*(exp_xth1-exp_xth2))/(4*sqrtpi*deltasth)
    10591084      qlth(ind1,ind2)=IntJ+IntI1+IntI2+IntI3
     1085      cth_vol(ind1,ind2)=IntJ_CF+IntI1_CF+IntI3_CF
    10601086      endif
    10611087
     1088
    10621089      qltot(ind1,ind2)=fraca(ind1,ind2)*qlth(ind1,ind2)+(1.-1.*fraca(ind1,ind2))*qlenv(ind1,ind2)
    1063 
     1090      ctot_vol(ind1,ind2)=fraca(ind1,ind2)*cth_vol(ind1,ind2)+(1.-1.*fraca(ind1,ind2))*cenv_vol(ind1,ind2)
    10641091
    10651092      ENDIF ! of if (iflag_cloudth_vert==1 or 3 or 4)
     1093
    10661094
    10671095      if (cenv(ind1,ind2).lt.1.e-10.or.cth(ind1,ind2).lt.1.e-10) then
    10681096      ctot(ind1,ind2)=0.
     1097      ctot_vol(ind1,ind2)=0.
    10691098      qcloud(ind1)=zqsatenv(ind1,ind2)
    10701099
     
    11001129      xenv=senv/(sqrt2*sigma1s)
    11011130      ctot(ind1,ind2)=0.5*(1.+1.*erf(xenv))
     1131      ctot_vol(ind1,ind2)=ctot(ind1,ind2)
    11021132      qltot(ind1,ind2)=sigma1s*((exp(-1.*xenv**2)/sqrt2pi)+xenv*sqrt2*cenv(ind1,ind2))
    11031133     
Note: See TracChangeset for help on using the changeset viewer.