Ignore:
Timestamp:
Sep 4, 2023, 4:35:35 PM (13 months ago)
Author:
evignon
Message:

inclusion des recents developpements sur la neige soufflee

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/surf_landice_mod.F90

    r4538 r4672  
    185185    REAL,DIMENSION(klon) :: precip_totsnow, evap_totsnow
    186186    REAL, DIMENSION (klon,6) :: alb6
    187     REAL                   :: rho0, rhoice, ustart0, hsalt, esalt, rhod
     187    REAL                   :: rho0, rhoice, ustart0,esalt, rhod
    188188    REAL                   :: lambdasalt,fluxsalt, csalt, nunu, aa, bb, cc
    189189    REAL                   :: tau_dens, tau_dens0, tau_densmin, rhomax, rhohard
    190     REAL, DIMENSION(klon)  :: ws1, rhos, ustart, qsalt
     190    REAL, DIMENSION(klon)  :: ws1, rhos, ustart, qsalt, hsalt, snowini
     191    REAL                   :: maxerosion ! in kg/s
     192
    191193! End definition
    192194!****************************************************************************************
     
    453455       ustart0 = 0.211
    454456       rhoice = 920.0
    455        rho0 = 200.0
     457       rho0 = 300.0
    456458       rhomax=450.0
    457        rhohard=400.0
     459       rhohard=450.0
    458460       tau_dens0=86400.0*10.  ! 10 days by default, in s
    459        tau_densmin=86400.0 ! 1 days according to in situ obs by C. Amory
     461       tau_densmin=21600.0    ! 1/4 days according to in situ obs by C. Amory during blowing snow +
     462                              ! Marshall et al. 1999 (snow densification during rain)
    460463
    461464       ! computation of threshold friction velocity
    462465       ! which depends on surface snow density
    463        do i = 1, knon
     466       do j = 1, knon
    464467           ! estimation of snow density
    465468           ! snow density increases with snow age and
    466            ! increases even faster in case of sedimentation of blowing snow
    467            tau_dens=max(tau_densmin, tau_dens0*exp(-abs(precip_bs(i))/pbst_bs-abs(precip_rain(i))/prt_bs))
    468            rhos(i)=rho0+(rhohard-rho0)*(1.-exp(-agesno(i)*86400.0/tau_dens))
     469           ! increases even faster in case of sedimentation of blowing snow or rain
     470           tau_dens=max(tau_densmin, & tau_dens0*exp(-abs(precip_bs(j))/pbst_bs-abs(precip_rain(j))/prt_bs) &
     471                    *exp(-max(tsurf(j)-272.0,0.)))
     472           rhos(j)=rho0+(rhohard-rho0)*(1.-exp(-agesno(j)*86400.0/tau_dens))
    469473           ! blowing snow flux formula used in MAR
    470            ws1(i)=(u1(i)**2+v1(i)**2)**0.5
    471            ustar(i)=(cdragm(i)*(u1(i)**2+v1(i)**2))**0.5
    472            ustart(i)=ustart0*exp(max(rhoice/rho0-rhoice/rhos(i),0.))*exp(max(0.,rhos(i)-rhomax))
     474           ws1(j)=(u1(j)**2+v1(j)**2)**0.5
     475           ustar(j)=(cdragm(j)*(u1(j)**2+v1(j)**2))**0.5
     476           ustart(j)=ustart0*exp(max(rhoice/rho0-rhoice/rhos(j),0.))*exp(max(0.,rhos(j)-rhomax))
    473477           ! we have multiplied by exp to prevent erosion when rhos>rhomax (usefull till
    474478           ! rhohard<450)
     
    486490          cc=2.0
    487491          lambdasalt=0.45
    488           do i =1, knon
    489                rhod=p1lay(i)/RD/temp_air(i)
    490                nunu=max(ustar(i)/ustart(i),1.e-3)
    491                fluxsalt=rhod/RG*(ustar(i)**3)*(1.-nunu**(-2)) * &
     492          do j =1, knon
     493               rhod=p1lay(j)/RD/temp_air(j)
     494               nunu=max(ustar(j)/ustart(j),1.e-3)
     495               fluxsalt=rhod/RG*(ustar(j)**3)*(1.-nunu**(-2)) * &
    492496                        (aa+bb*nunu**(-2)+cc*nunu**(-1)) 
    493                csalt=fluxsalt/(2.8*ustart(i))
    494                hsalt=0.08436*ustar(i)**1.27
    495                qsalt(i)=1./rhod*csalt*lambdasalt*RG/(max(ustar(i)**2,1E-6)) &
    496                        * exp(-lambdasalt*RG*hsalt/max(ustar(i)**2,1E-6))
    497                qsalt(i)=max(qsalt(i),0.)
     497               csalt=fluxsalt/(2.8*ustart(j))
     498               hsalt(j)=0.08436*ustar(j)**1.27
     499               qsalt(j)=1./rhod*csalt*lambdasalt*RG/(max(ustar(j)**2,1E-6)) &
     500                       * exp(-lambdasalt*RG*hsalt(j)/max(ustar(j)**2,1E-6))
     501               qsalt(j)=max(qsalt(j),0.)
    498502          enddo
    499503
     
    501505       else
    502506       ! default formulation from MAR model (Amory et al. 2021, Gallee et al. 2001)       
    503           do i=1, knon
    504               esalt=1./(3.25*max(ustar(i),0.001))
    505               hsalt=0.08436*ustar(i)**1.27
    506               qsalt(i)=(max(ustar(i)**2-ustart(i)**2,0.))/(RG*hsalt)*esalt
    507               !ep=qsalt*cdragm(i)*sqrt(u1(i)**2+v1(i)**2)
     507          do j=1, knon
     508              esalt=1./(3.25*max(ustar(j),0.001))
     509              hsalt(j)=0.08436*ustar(j)**1.27
     510              qsalt(j)=(max(ustar(j)**2-ustart(j)**2,0.))/(RG*hsalt(j))*esalt
     511              !ep=qsalt*cdragm(j)*sqrt(u1(j)**2+v1(j)**2)
    508512          enddo
    509513       endif
    510514
    511         ! calculation of erosion (emission flux towards the first atmospheric level)
     515        ! calculation of erosion (flux positive towards the surface here)
    512516        ! consistent with implicit resolution of turbulent mixing equation
    513        do i=1, knon
    514               rhod=p1lay(i)/RD/temp_air(i)
    515               fluxbs(i)=rhod*ws1(i)*cdragm(i)*zeta_bs*(AcoefQBS(i)-qsalt(i)) &
    516                        / (1.-rhod*ws1(i)*zeta_bs*cdragm(i)*BcoefQBS(i)*dtime)
    517               !fluxbs(i)= zeta_bs*rhod*ws1(i)*cdragm(i)*(qbs1(i)-qsalt(i))
    518        enddo
    519 
    520        ! for outputs
    521        do j = 1, knon
    522           i = knindex(j)
    523           zxustartlic(i) = ustart(j)
    524           zxrhoslic(i) = rhos(j)
     517       do j=1, knon
     518              i = knindex(j)
     519              rhod=p1lay(j)/RD/temp_air(j)
     520              ! Nemoto and Nishimura 2004 show that steady-state saltation is achieved within an interval of about 10s
     521              ! we thus prevent snowerosion (snow particle transfer from the saltation layer to the first model level)
     522              ! to exceed (in intensity) integrated over 10s to exceed the total mass of snow particle in the saltation layer
     523              ! (rho*qsalt*hsalt)
     524              maxerosion=hsalt(j)*qsalt(j)*rhod/10.
     525              fluxbs(j)=rhod*ws1(j)*cdragm(j)*(AcoefQBS(j)-qsalt(j)) &
     526                       / (1.-rhod*ws1(j)*cdragm(j)*BcoefQBS(j)*dtime)
     527              !fluxbs(j)= rhod*ws1(j)*cdragm(j)*(qbs1(j)-qsalt(j))
     528              fluxbs(j)=max(-maxerosion,fluxbs(j))
     529
     530              ! for outputs
     531
     532              zxustartlic(i) = ustart(j)
     533              zxrhoslic(i) = rhos(j)
    525534       enddo
    526535
Note: See TracChangeset for help on using the changeset viewer.