Ignore:
Timestamp:
May 11, 2023, 10:53:52 AM (17 months ago)
Author:
evignon
Message:

nouvelle formulation du flux d'emission de neige soufflee

Location:
LMDZ6/trunk/libf/phylmdiso
Files:
2 edited

Legend:

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

    r4523 r4529  
    24742474                  AcoefH, AcoefQ, BcoefH, BcoefQ, &
    24752475                  AcoefU, AcoefV, BcoefU, BcoefV, &
     2476                  AcoefQBS, BcoefQBS, &
    24762477                  ypsref, yu1, yv1, ygustiness, yrugoro, pctsrf, &
    24772478                  ysnow, yqsurf, yqsol,yqbs1, yagesno, &
  • LMDZ6/trunk/libf/phylmdiso/surf_landice_mod.F90

    r4528 r4529  
    1515       AcoefH, AcoefQ, BcoefH, BcoefQ, &
    1616       AcoefU, AcoefV, BcoefU, BcoefV, &
     17       AcoefQBS, BcoefQBS, &
    1718       ps, u1, v1, gustiness, rugoro, pctsrf, &
    1819       snow, qsurf, qsol, qbs1, agesno, &
     
    4950!FC
    5051    USE ioipsl_getin_p_mod, ONLY : getin_p
    51     USE blowing_snow_ini_mod, ONLY : zeta_bs, pbst_bs, prt_bs
     52    USE blowing_snow_ini_mod, ONLY : zeta_bs, pbst_bs, prt_bs, iflag_saltation_bs
    5253
    5354#ifdef CPP_INLANDSIS
     
    7879    REAL, DIMENSION(klon), INTENT(IN)             :: BcoefH, BcoefQ
    7980    REAL, DIMENSION(klon), INTENT(IN)             :: AcoefU, AcoefV, BcoefU, BcoefV
     81    REAL, DIMENSION(klon), INTENT(IN)             :: AcoefQBS, BcoefQBS
    8082    REAL, DIMENSION(klon), INTENT(IN)             :: ps
    8183    REAL, DIMENSION(klon), INTENT(IN)             :: u1, v1, gustiness, qbs1
     
    183185    REAL,DIMENSION(klon) :: precip_totsnow, evap_totsnow
    184186    REAL, DIMENSION (klon,6) :: alb6
    185     REAL                   :: rho0, rhoice, ustart0, hsalt, esalt, qsalt
     187    REAL                   :: rho0, rhoice, ustart0, hsalt, esalt, rhod
     188    REAL                   :: lambdasalt,fluxsalt, csalt, nunu, aa, bb, cc
    186189    REAL                   :: tau_dens, tau_dens0, tau_densmin, rhomax, rhohard
    187     REAL, DIMENSION(klon)  :: ws1, rhos, ustart
     190    REAL, DIMENSION(klon)  :: ws1, rhos, ustart, qsalt
    188191! End definition
    189192!****************************************************************************************
     
    455458       tau_dens0=86400.0*10.  ! 10 days by default, in s
    456459       tau_densmin=86400.0 ! 1 days according to in situ obs by C. Amory
     460
     461       ! computation of threshold friction velocity
     462       ! which depends on surface snow density
    457463       do i = 1, knon
    458464           ! estimation of snow density
     
    467473           ! we have multiplied by exp to prevent erosion when rhos>rhomax (usefull till
    468474           ! rhohard<450)
    469            esalt=1./(3.25*max(ustar(i),0.001))
    470            hsalt=0.08436*ustar(i)**1.27
    471            qsalt=(max(ustar(i)**2-ustart(i)**2,0.))/(RG*hsalt)*esalt
    472            !ep=qsalt*cdragm(i)*sqrt(u1(i)**2+v1(i)**2)
    473            fluxbs(i)= zeta_bs*p1lay(i)/RD/temp_air(i)*ws1(i)*cdragm(i)*(qbs1(i)-qsalt)
     475       enddo
     476       
     477       ! computation of qbs at the top of the saltation layer
     478       ! two formulations possible
     479       ! pay attention that qbs is a mixing ratio and has to be converted
     480       ! to specific content
     481       
     482       if (iflag_saltation_bs .eq. 1) then
     483       ! expression from CRYOWRF (Sharma et al. 2022)
     484          aa=2.6
     485          bb=2.5
     486          cc=2.0
     487          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                        (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.)
     498          enddo
     499
     500
     501       else
     502       ! 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)
     508          enddo
     509       endif
     510
     511        ! calculation of erosion (emission flux towards the first atmospheric level)
     512        ! 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*BcoefQBS(i)*dtime)
     517              !fluxbs(i)= zeta_bs*rhod*ws1(i)*cdragm(i)*(qbs1(i)-qsalt(i))
    474518       enddo
    475519
Note: See TracChangeset for help on using the changeset viewer.