Ignore:
Timestamp:
Apr 26, 2022, 3:37:00 PM (3 years ago)
Author:
bclmd
Message:

Adding calculation of viscosity/molrad, general stokes law and non-spherical water ice particles in newsedim.F

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/newsedim.F

    r1384 r2670  
    11      SUBROUTINE newsedim(ngrid,nlay,naersize,ptimestep,
    2      &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq)
     2     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,iq)
    33     
     4      use ioipsl_getin_p_mod, only: getin_p
    45      use comcstfi_mod, only: r, g
     6      use gases_h
     7      use tracer_h, only : igcm_h2o_ice
     8      use watercommon_h, only: T_h2O_ice_liq,T_h2O_ice_clouds     
     9      use radii_mod, only: h2o_cloudrad
     10
    511      IMPLICIT NONE
    612
     
    3440      real,intent(inout) :: pqi(ngrid,nlay)  ! tracer   (e.g. ?/kg)
    3541      real,intent(out) :: wq(ngrid,nlay+1)  ! flux of tracer during timestep (?/m-2)
    36      
     42      integer,intent(in) :: iq ! tracer index
     43
    3744c   local:
    3845c   ------
    3946
    40       INTEGER l,ig, k, i
    41       REAL rfall
     47      INTEGER l,ig, k, i, igas
     48      REAL rfall, rsurf, Reynolds, Cd, zfrac
     49      REAL reffh2oliq(ngrid,nlay), reffh2oice(ngrid,nlay)
    4250
    4351      LOGICAL,SAVE :: firstcall=.true.
    4452!$OMP THREADPRIVATE(firstcall)
     53      LOGICAL,SAVE :: crystal_shape
     54!$OMP THREADPRIVATE(crystal_shape)     
    4555
    4656c    Traceurs :
     
    5565c    ~~~~~~~~~~~~~~~~~
    5666c     Gas molecular viscosity (N.s.m-2)
    57       real,parameter :: visc=1.e-5       ! CO2
     67      real, allocatable, save :: visc(:,:)
     68!$OMP THREADPRIVATE(visc)     
    5869c     Effective gas molecular radius (m)
    59       real,parameter :: molrad=2.2e-10   ! CO2
     70      real,save :: molrad
    6071
    6172c     local and saved variable
     
    6677c       --------------------------
    6778
    68 
    6979      !print*,'temporary fixed particle rad in newsedim!!'
    7080
     
    7282         firstcall=.false.
    7383
     84c        Determination of the viscosity a(N.s.m-2) and the mean molecular radius (m)
     85        write(*,*) "Calculation of the viscosity and the mean molecular"
     86     &               ," radius from gases.def"
     87         allocate(visc(ngrid,nlay))
     88         visc(:,:)=0.0
     89         molrad=0.
     90         do igas=1, ngasmx
     91           if(gfrac(igas).ge.0.0) then
     92             if(igas.eq.igas_CO2) then
     93               molrad = molrad + gfrac(igas)*2.2e-10                              ! CO2
     94               visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! CO2
     95             elseif(igas.eq.igas_N2) then
     96               molrad = molrad + gfrac(igas)*1.8e-10                              ! N2 (Kunze et al. 2022)
     97               visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! N2
     98             elseif(igas.eq.igas_H2) then
     99               molrad = molrad + gfrac(igas)*1.41e-10                             ! H2 (Ackerman & Marley 2001)
     100               visc(:,:) = visc(:,:) + gfrac(igas)*2.0d-07*pt(:,:)**0.66          ! H2 (from Rosner 2000)
     101             elseif(igas.eq.igas_H2O) then
     102               molrad = molrad + gfrac(igas)*2.3e-10                              ! H2O (Crifo 1989 at 300K)
     103               visc(:,:) = visc(:,:) + gfrac(igas)*8e-6                           ! H2O (Sengers & Kamgar-Parsi 1984)
     104             elseif(igas.eq.igas_He) then
     105               molrad = molrad + gfrac(igas)*1.1e-10                              ! He (Kunze et al. 2022)
     106               visc(:,:) = visc(:,:) +                                            ! He
     107     &                     gfrac(igas)*1.9e-5*(pt(:,:)/273.15)**0.7               ! He (Petersen 1970)
     108             elseif(igas.eq.igas_CH4) then
     109               molrad = molrad + gfrac(igas)*1.9e-10                              ! CH4 (Ismail et al. 2015)
     110               visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! CH4
     111             else
     112               molrad = molrad + gfrac(igas)*2.2e-10                              ! CO2 by default
     113               visc(:,:) = visc(:,:) + gfrac(igas)*1.e-5                          ! CO2 by default
     114               write(*,*) trim(gnom(igas))," is not included in"
     115     &              ," newsedim, CO2 is used by default"
     116             endif
     117           endif
     118         enddo
     119         write(*,*) "visc(1,1)=",visc(1,1),"N.s.m-2; ",
     120     &               "molrad=",molrad,"m"
     121
     122c Correction for non-spherical water ice particles
     123         write(*,*) "Use non-spherical water ice particles",
     124     &             " for the sedimentation ?"
     125         crystal_shape=.false. !default
     126         call getin_p("crystal_shape",crystal_shape)
     127         write(*,*) " crystal_shape = ",crystal_shape
    74128
    75129
     
    78132
    79133!       - Constant to compute stokes speed simple formulae
    80 !        (Vstokes =  b * rho* r**2   avec   b= (2/9) * rho * g / visc
    81          b = 2./9. * g / visc
     134!        (Vstokes =  b / visc * rho* r**2   avec   b= (2/9) * rho * g
     135         b = 2./9. * g
    82136
    83137!       - Constant  to compute gas mean free path
     
    100154c     (stokes law corrected for low pressure by the Cunningham
    101155c     slip-flow correction  according to Rossow (Icarus 36, 1-50, 1978)
    102        
     156
     157c Compute liquid and ice particle radii
     158        if((iq.eq.igcm_h2o_ice).and.crystal_shape) then
     159            call h2o_cloudrad(ngrid,nlay,pqi,reffh2oliq,reffh2oice)
     160        endif
     161
     162
    103163        do  l=1,nlay
    104164          do ig=1, ngrid
     
    110170            endif 
    111171
    112             vstokes(ig,l) = b * rho * rfall**2 *
    113      &      (1 + 1.333* ( a*pt(ig,l)/pplev(ig,l) )/rfall)
     172c Correction for non-spherical water ice particles           
     173            if((iq.eq.igcm_h2o_ice).and.crystal_shape) then
     174              zfrac= (pt(ig,l)-T_h2O_ice_clouds) /
     175     &               (T_h2O_ice_liq-T_h2O_ice_clouds)
     176              zfrac= MAX(zfrac, 0.0)
     177              zfrac= MIN(zfrac, 1.0)
     178              rsurf=max(reffh2oice(ig,l),45.6*reffh2oice(ig,l)**1.3)        ! surface radius (formula for rimed dendrites from Hemsfield 1977, transition at around 30 microns)
     179              rsurf=1/(zfrac/reffh2oice(ig,l)+(1-zfrac)/rsurf)              ! radius giving the mean velocity between liquid and ice particles
     180            else
     181              rsurf=rfall
     182            endif
     183
     184            vstokes(ig,l) = b / visc(ig,l) * rho * rfall**3 / rsurf *
     185     &      (1 + 1.333* ( a*pt(ig,l)/pplev(ig,l) )/rsurf)
     186
     187c Correction for high Reynolds number
     188            Reynolds=2. * pplev(ig,l) / r / pt(ig,l) *
     189     &        rsurf * vstokes(ig,l) / visc(ig,l)
     190            if(Reynolds.ge.1.0) then
     191              do i=1,5
     192              Cd=24. / Reynolds * (1. + 0.15 * Reynolds**0.687) +
     193     &           0.42 / (1. + 42500 / Reynolds**1.16)                       ! (Formula from Bagheri 2018)
     194              vstokes(ig,l) =(8./3.*pplev(ig,l)/r/pt(ig,l)*g*rfall**3 /
     195     &           rsurf**2/rho/Cd *
     196     &           (1.+1.333*(a*pt(ig,l)/pplev(ig,l))/rsurf))**0.5
     197              Reynolds=2. * pplev(ig,l) / r / pt(ig,l) *
     198     &           rsurf * vstokes(ig,l) / visc(ig,l)
     199              enddo
     200            endif   
    114201
    115202c           Layer crossing time (s) :
Note: See TracChangeset for help on using the changeset viewer.