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

nouvelle formulation du flux d'emission de neige soufflee

File:
1 edited

Legend:

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

    r4526 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, &
     
    3435!FC
    3536    USE ioipsl_getin_p_mod, ONLY : getin_p
    36     USE blowing_snow_ini_mod, ONLY : zeta_bs, pbst_bs, prt_bs
     37    USE blowing_snow_ini_mod, ONLY : zeta_bs, pbst_bs, prt_bs, iflag_saltation_bs
    3738
    3839#ifdef CPP_INLANDSIS
     
    6263    REAL, DIMENSION(klon), INTENT(IN)             :: BcoefH, BcoefQ
    6364    REAL, DIMENSION(klon), INTENT(IN)             :: AcoefU, AcoefV, BcoefU, BcoefV
     65    REAL, DIMENSION(klon), INTENT(IN)             :: AcoefQBS, BcoefQBS
    6466    REAL, DIMENSION(klon), INTENT(IN)             :: ps
    6567    REAL, DIMENSION(klon), INTENT(IN)             :: u1, v1, gustiness, qbs1
     
    138140    REAL,DIMENSION(klon) :: precip_totsnow, evap_totsnow
    139141    REAL, DIMENSION (klon,6) :: alb6
    140     REAL                   :: rho0, rhoice, ustart0, hsalt, esalt, qsalt
     142    REAL                   :: rho0, rhoice, ustart0, hsalt, esalt, rhod
     143    REAL                   :: lambdasalt,fluxsalt, csalt, nunu, aa, bb, cc
    141144    REAL                   :: tau_dens, tau_dens0, tau_densmin, rhomax, rhohard
    142     REAL, DIMENSION(klon)  :: ws1, rhos, ustart
     145    REAL, DIMENSION(klon)  :: ws1, rhos, ustart, qsalt
    143146! End definition
    144147!****************************************************************************************
     
    366369       tau_dens0=86400.0*10.  ! 10 days by default, in s
    367370       tau_densmin=86400.0 ! 1 days according to in situ obs by C. Amory
     371
     372       ! computation of threshold friction velocity
     373       ! which depends on surface snow density
    368374       do i = 1, knon
    369375           ! estimation of snow density
     
    378384           ! we have multiplied by exp to prevent erosion when rhos>rhomax (usefull till
    379385           ! rhohard<450)
    380            esalt=1./(3.25*max(ustar(i),0.001))
    381            hsalt=0.08436*ustar(i)**1.27
    382            qsalt=(max(ustar(i)**2-ustart(i)**2,0.))/(RG*hsalt)*esalt
    383            !ep=qsalt*cdragm(i)*sqrt(u1(i)**2+v1(i)**2)
    384            !Pay attention that this is an explicit formulation for the surface flux
    385            !Formulation fully consistent with the implicit resolution of the turbulent
    386            !mixing scheme remains to be coded
    387            fluxbs(i)= zeta_bs*p1lay(i)/RD/temp_air(i)*ws1(i)*cdragm(i)*(qbs1(i)-qsalt)
     386       enddo
     387       
     388       ! computation of qbs at the top of the saltation layer
     389       ! two formulations possible
     390       ! pay attention that qbs is a mixing ratio and has to be converted
     391       ! to specific content
     392       
     393       if (iflag_saltation_bs .eq. 1) then
     394       ! expression from CRYOWRF (Sharma et al. 2022)
     395          aa=2.6
     396          bb=2.5
     397          cc=2.0
     398          lambdasalt=0.45
     399          do i =1, knon
     400               rhod=p1lay(i)/RD/temp_air(i)
     401               nunu=max(ustar(i)/ustart(i),1.e-3)
     402               fluxsalt=rhod/RG*(ustar(i)**3)*(1.-nunu**(-2)) * &
     403                        (aa+bb*nunu**(-2)+cc*nunu**(-1)) 
     404               csalt=fluxsalt/(2.8*ustart(i))
     405               hsalt=0.08436*ustar(i)**1.27
     406               qsalt(i)=1./rhod*csalt*lambdasalt*RG/(max(ustar(i)**2,1E-6)) &
     407                       * exp(-lambdasalt*RG*hsalt/max(ustar(i)**2,1E-6))
     408               qsalt(i)=max(qsalt(i),0.)
     409          enddo
     410
     411
     412       else
     413       ! default formulation from MAR model (Amory et al. 2021, Gallee et al. 2001)       
     414          do i=1, knon
     415              esalt=1./(3.25*max(ustar(i),0.001))
     416              hsalt=0.08436*ustar(i)**1.27
     417              qsalt(i)=(max(ustar(i)**2-ustart(i)**2,0.))/(RG*hsalt)*esalt
     418              !ep=qsalt*cdragm(i)*sqrt(u1(i)**2+v1(i)**2)
     419          enddo
     420       endif
     421
     422        ! calculation of erosion (emission flux towards the first atmospheric level)
     423        ! consistent with implicit resolution of turbulent mixing equation
     424       do i=1, knon
     425              rhod=p1lay(i)/RD/temp_air(i)
     426              fluxbs(i)=rhod*ws1(i)*cdragm(i)*zeta_bs*(AcoefQBS(i)-qsalt(i)) &
     427                       / (1.-rhod*ws1(i)*zeta_bs*BcoefQBS(i)*dtime)
     428              !fluxbs(i)= zeta_bs*rhod*ws1(i)*cdragm(i)*(qbs1(i)-qsalt(i))
    388429       enddo
    389430
Note: See TracChangeset for help on using the changeset viewer.