Ignore:
Timestamp:
Sep 19, 2012, 12:27:11 PM (12 years ago)
Author:
jleconte
Message:

19/09/2012 == JL

  • Correction in largescale to improve robustness when large water vapor amount
  • Correction in soil_setting to allow change of the number of subsurface layers


Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/ave_stelspec.F90

    r785 r786  
    152152         band=1
    153153         Do while(lam(1).lt. real(10000.0/BWNV(band+1)))
    154             if (band+1.ge.L_NSPECTV+1) exit
     154            if (band.gt.L_NSPECTV-1) exit
    155155            band=band+1
    156156         enddo
  • trunk/LMDZ.GENERIC/libf/phystd/dimphys.h

    r253 r786  
    99! nsoilmx : number of subterranean layers
    1010      !integer, parameter :: nsoilmx = 4 ! for a test
    11       integer, parameter :: nsoilmx = 18 ! for z1=0.02 cm, depth = 104.8 m
     11      integer, parameter :: nsoilmx = 18 ! for z1=0.0002 cm, depth = 18 m => mars case
     12      !integer, parameter :: nsoilmx = 13 ! for z1=0.03 cm, depth = 104.8 m => earth case
    1213!-----------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/largescale.F90

    r773 r786  
    5151      EXTERNAL CBRT
    5252      INTEGER i, k , nn
    53       INTEGER,PARAMETER :: niter=4
     53      INTEGER,PARAMETER :: nitermax=1000
     54      REAL,PARAMETER :: alpha=.5,qthreshold=1.e-6
    5455      REAL zt(ngridmx), zq(ngridmx)
    5556      REAL zcond(ngridmx),zcond_iter
     
    9293
    9394         if(zt(i).le.15.) then
    94             print*,'in lsc',i,zt(i)
    95             zt(i)=15.   ! check too low temperatures
     95            print*,'in lsc',i,k,zt(i)
     96!           zt(i)=15.   ! check too low temperatures
    9697         endif
    97 !         call watersat(zt(i),pplay(i,k),zqs(i))
    9898         call Psat_water(zt(i),pplay(i,k),psat_tmp,zqs(i))
    9999 
    100          zdelq(i) = ratqs * zq(i)
    101          if(zq(i)+zdelq(i).lt.0.999) then
    102             rneb(i,k) = (zq(i)+zdelq(i)-zqs(i)) / (2.0*zdelq(i))
     100         zdelq(i) = MAX(MIN(ratqs * zq(i),1.-zq(i)),1.e-12)
     101         rneb(i,k) = (zq(i)+zdelq(i)-zqs(i)) / (2.0*zdelq(i))
     102!        print*,zq(i),zdelq(i),zqs(i),rneb(i,k)
     103         if (rneb(i,k).lt.0.) then  !no clouds
     104
     105            rneb(i,k)=0.
     106            zcond(i)=0.
     107
     108         else if (rneb(i,k).gt.1.) then    !complete cloud cover, we start without evaporating
     109
     110            rneb(i,k)=1.
     111            zt(i)=pt(i,k)+pdt(i,k)*ptimestep
     112            zx_q(i) = pq(i,k,igcm_h2o_vap)+pdq(i,k,igcm_h2o_vap)*ptimestep
     113            dqevap(i,k)=0.
     114!           iterative process to stabilize the scheme when large water amounts JL12
     115            zcond(i) = 0.0
     116            Do nn=1,nitermax 
     117               call Psat_water(zt(i),pplay(i,k),psat_tmp,zqs(i))
     118               call Lcpdqsat_water(zt(i),pplay(i,k),psat_tmp,zqs(i),zdqs(i))
     119               zcond_iter = alpha*(zx_q(i)-zqs(i))/(1.+zdqs(i))   
     120                  !zcond can be negative here
     121               zx_q(i) = zx_q(i) - zcond_iter
     122               zcond(i) = zcond(i) + zcond_iter
     123               zt(i) = zt(i) + zcond_iter*RLVTT/RCPD
     124               if (ABS(zcond_iter/alpha).lt.qthreshold) exit
     125            End do ! niter
     126            zcond(i)=MAX(zcond(i),-(pq(i,k,igcm_h2o_ice)+pdq(i,k,igcm_h2o_ice)*ptimestep))
     127
     128         else   !standard case     
     129
    103130            zx_q(i) = (zq(i)+zdelq(i)+zqs(i))/2.0 !water vapor in cloudy sky
    104             if (rneb(i,k) .LE. 0.0) zx_q(i) = 0.0
    105             if (rneb(i,k) .GE. 1.0) zx_q(i) = zq(i)
    106             rneb(i,k) = MAX(0.0,MIN(1.0,rneb(i,k)))
    107          else
    108             if(zq(i).gt.zqs(i)) then
    109                rneb(i,k)=1.
    110                zx_q(i)=zq(i)
    111             else
    112                rneb(i,k)=0.
    113                zx_q(i)=zqs(i)  !no condensation needed
    114             Endif
     131!           iterative process to stabilize the scheme when large water amounts JL12
     132            zcond(i) = 0.0
     133            Do nn=1,nitermax 
     134               call Lcpdqsat_water(zt(i),pplay(i,k),psat_tmp,zqs(i),zdqs(i))
     135               zcond_iter = MAX(0.0,alpha*(zx_q(i)-zqs(i))/(1.+zdqs(i)))           
     136                  !zcond always postive! cannot evaporate clouds!
     137                  !this is why we must reevaporate before largescale
     138               zx_q(i) = zx_q(i) - zcond_iter
     139               zcond(i) = zcond(i) + zcond_iter
     140               if (ABS(zcond_iter/alpha).lt.qthreshold) exit
     141               zt(i) = zt(i) + zcond_iter*RLVTT/RCPD
     142               call Psat_water(zt(i),pplay(i,k),psat_tmp,zqs(i))
     143            End do ! niter
     144
    115145         Endif
    116146
    117 !        iterative process to stabilize the scheme when large water amounts JL12
    118          zcond(i) = 0.0
    119          Do nn=1,niter 
    120 !            call watersat_grad(zt(i),zqs(i),zdqs(i))
    121             call Lcpdqsat_water(zt(i),pplay(i,k),psat_tmp,zqs(i),zdqs(i))
    122             zcond_iter = MAX(0.0,(zx_q(i)-zqs(i))*rneb(i,k)/(1.+zdqs(i)))         
    123                !zcond always postive! cannot evaporate clouds!
    124                !this is why we must reevaporate before largescale
    125             zx_q(i) = zx_q(i) - zcond_iter
    126             zcond(i) = zcond(i) + zcond_iter
    127             zt(i) = zt(i) + zcond_iter*RLVTT/RCPD
    128             call Psat_water(zt(i),pplay(i,k),psat_tmp,zqs(i))
    129          End do ! niter
     147         zcond(i) = zcond(i)*rneb(i,k)/ptimestep ! JL12
    130148
    131 
    132          zcond(i) = zcond(i)/ptimestep ! added by RDW
    133149      ENDDO
    134150
  • trunk/LMDZ.GENERIC/libf/phystd/mass_redistribution.F90

    r728 r786  
    146146                  zmassboil(ig)=pqs(ig,igcm_h2o_vap)/ptimestep
    147147               endif
    148                zmassboil(ig)=zmassboil(ig)*0.3 !momentary, should be 1. JL12
     148               zmassboil(ig)=zmassboil(ig)*0.0 !momentary, should be 1. JL12
    149149               pdqsmr(ig,igcm_h2o_vap)=-zmassboil(ig)
    150150               pdtsrfmr(ig)=-zmassboil(ig)*RLVTT/pcapcal(ig)
  • trunk/LMDZ.GENERIC/libf/phystd/soil_settings.F

    r135 r786  
    133133        ! read <depth> coordinate
    134134        if (interpol) then !put values in oldmlayer
     135          if (.not.allocated(oldmlayer)) then
     136             allocate(oldmlayer(dimlen),stat=ierr)
     137          endif
    135138#ifdef NC_DOUBLE
    136139           ierr = NF_GET_VAR_DOUBLE(nid,nvarid,oldmlayer)
     
    159162      ! default mlayer distribution, following a power law:
    160163      !  mlayer(k)=lay1*alpha**(k-1/2)
    161         lay1=2.e-4
     164        lay1=2.e-4  !mars case (nsoilmx=18)
     165!        lay1=3.e-2  !earth case (nsoilmx=13)
    162166        alpha=2
    163167        do iloop=0,nsoil-1
  • trunk/LMDZ.GENERIC/libf/phystd/watercommon_h.F90

    r728 r786  
    5151         real,parameter :: Trefvaporization=35.86
    5252         real,parameter :: Trefsublimation=7.66
     53         real,parameter :: Tmin=8.
    5354         real,parameter :: r3vaporization=17.269
    5455         real,parameter :: r3sublimation=21.875
     
    5657! checked vs. old watersat data 14/05/2012 by JL.
    5758
    58          if (T.lt.T_h2O_ice_liq) then ! solid / vapour
    59             psat = Pref_solid_liquid*Exp(r3sublimation*(T-T_h2O_ice_liq)/(T-Trefsublimation))
    60          else                 ! liquid / vapour
    61             psat = Pref_solid_liquid*Exp(r3vaporization*(T-T_h2O_ice_liq)/(T-Trefvaporization))
     59         if (T.gt.T_h2O_ice_liq) then
     60            psat = Pref_solid_liquid*Exp(r3vaporization*(T-T_h2O_ice_liq)/(T-Trefvaporization)) ! liquid / vapour
     61         else if (T.lt.Tmin) then
     62            print*, "careful, T<Tmin in psat water"
     63            psat = Pref_solid_liquid*Exp(r3sublimation*(Tmin-T_h2O_ice_liq)/(Tmin-Trefsublimation)) ! min psat 
     64         else                 
     65            psat = Pref_solid_liquid*Exp(r3sublimation*(T-T_h2O_ice_liq)/(T-Trefsublimation)) ! solid / vapour
    6266         endif
    6367         if(psat.gt.p) then
     
    99103         real,parameter :: Pref_solid_liquid=611.14
    100104         real,parameter :: Trefvaporization=35.86
     105         real,parameter :: Tmin=8.
    101106         real,parameter :: Trefsublimation=7.66
    102107         real,parameter :: r3vaporization=17.269
     
    110115         endif
    111116
    112          if (T.lt.T_h2O_ice_liq) then ! solid / vapour
    113             dummy = r3sublimation*(T_h2O_ice_liq-Trefsublimation)/(T-Trefsublimation)**2
    114          else                 ! liquid / vapour
    115             dummy = r3vaporization*(T_h2O_ice_liq-Trefvaporization)/(T-Trefvaporization)**2
     117         if (T.gt.T_h2O_ice_liq) then
     118            dummy = r3vaporization*(T_h2O_ice_liq-Trefvaporization)/(T-Trefvaporization)**2  ! liquid / vapour
     119         else if (T.lt.Tmin) then
     120            print*, "careful, T<Tmin in Lcp psat water"
     121            dummy = r3sublimation*(T_h2O_ice_liq-Trefsublimation)/(Tmin-Trefsublimation)**2  ! solid / vapour
     122         else               
     123            dummy = r3sublimation*(T_h2O_ice_liq-Trefsublimation)/(T-Trefsublimation)**2  ! solid / vapour
    116124         endif
    117125
    118          dqsat=RLVTT/RCPD*qsat**2*(p/(epsi*psat))*dummy
     126         dqsat=RLVTT/RCPD*qsat*(p/(p-(1.-epsi)*psat))*dummy
    119127         return
    120128      end subroutine Lcpdqsat_water
Note: See TracChangeset for help on using the changeset viewer.