Ignore:
Timestamp:
Oct 3, 2025, 4:20:48 PM (8 weeks ago)
Author:
mmaurice
Message:

Generic PCM:

Add time-dependent dust scenario for (present-day) Mars from Montmessin
et al., 2004.

MM

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

Legend:

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

    r3893 r3922  
    55contains
    66
    7       Subroutine aeropacity(ngrid,nlayer,nq,pplay,pplev,pt, pq, &
     7      Subroutine aeropacity(ngrid,nlayer,nq,pplay,pplev,pt,pq,zls, &
    88         aerosol,reffrad,nueffrad, QREFvis3d,QREFir3d,tau_col, &
    99         cloudfrac,totcloudfrac,clearsky)
     
    2020       use geometry_mod, only: latitude
    2121       use callkeys_mod, only: aerofixco2,aerofixh2o,kastprof,cloudlvl, &
    22                 CLFvarying,CLFfixval,dusttau,                           &
     22                CLFvarying,CLFfixval,dusttau,timedepdust,                       &
    2323                pres_bottom_tropo,pres_top_tropo,obs_tau_col_tropo,     &
    2424                pres_bottom_strato,pres_top_strato,obs_tau_col_strato,  &
     
    6969      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! inter-layer pressure (Pa)
    7070      REAL,INTENT(IN) :: pq(ngrid,nlayer,nq) ! tracers (.../kg_of_air)
     71      REAL,INTENT(IN) :: zls ! Stellar longitude (rad)
    7172      REAL,INTENT(IN) :: pt(ngrid,nlayer) ! mid-layer temperature (K)
    7273      REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind) ! aerosol optical depth
     
    100101      CHARACTER(LEN=20) :: tracername ! to temporarily store text
    101102
    102       ! for fixed dust profiles
     103      ! for dust profiles
    103104      real topdust, expfactor, zp
    104105      REAL taudusttmp(ngrid) ! Temporary dust opacity used before scaling
    105106      REAL tauh2so4tmp(ngrid) ! Temporary h2so4 opacity used before scaling
     107
     108      ! time-dependent dust (MM)
     109      real zlsconst, odpref, taueq, tauS, tauN
     110      real tau_pref_MGS(ngrid), tauscaling(ngrid)
    106111
    107112      real CLFtot
     
    311316!==================================================================
    312317!             Dust
     318!             Either constant/homogeneous or
     319!             following MGS scenario for
     320!             present-day Mars as per:
     321!             Montmessin et al., 2004
     322!             (DOI: 10.1029/2004JE002284)
    313323!==================================================================
    314324      if (iaero_dust.ne.0) then
     
    316326!         1. Initialization
    317327          aerosol(1:ngrid,1:nlayer,iaer)=0.0
    318          
    319           topdust=30.0 ! km  (used to be 10.0 km) LK
    320 
    321 !       2. Opacity calculation
     328
     329!       2. Opacity calculation
     330
     331          IF (timedepdust) THEN
     332!           Time-dependent dust (MGS scenarion for present-day Mars)
     333
     334            zlsconst = sin(zls-2.76)
     335            taudusttmp(:) = 0
     336            odpref = 610. ! Reference pressure (Pa) of
     337                          ! DOD (Dust optical Depth) tau_pref_*
     338
     339            DO l=1,nlayer-1
     340              DO ig=1,ngrid
     341
     342                  topdust = 60.+18.*zlsconst                     & ! From
     343                    - (32.+18.*zlsconst)*(sin(latitude(ig)))**4  & ! Montmessin
     344                    -  8.*zlsconst*(sin(latitude(ig)))**5          ! et al. 2004
     345                  if (pplay(ig,l).ge.odpref/(988.**(topdust/70.))) then ! What is the use of this line?
     346                    zp = (odpref/pplay(ig,l))**(70./topdust)
     347                    expfactor = max(exp(0.007*(1.-max(zp,1.))),1.e-3)
     348                  else
     349                    expfactor = 1.e-3
     350                  endif
     351
     352!                 Vertical scaling function
     353                  aerosol(ig,l,iaer) = (pplev(ig,l)-pplev(ig,l+1)) &
     354                                     *  expfactor
     355
     356!                 Horizontal scaling of the dust opacity
     357                  if (l==1) then
     358
     359                    taueq = 0.2 + (0.5-0.2) * (cos(0.5*(zls-4.363)))**14
     360                    tauS  = 0.1 + (0.5-0.1) * (cos(0.5*(zls-4.363)))**14
     361                    tauN  = 0.1
     362
     363                    if (latitude(ig).ge.0) then
     364                    ! Northern hemisphere
     365                      tau_pref_MGS(ig) = tauN + (taueq-tauN)*0.5 &
     366                             *(1+tanh((45-latitude(ig)*180./pi)*6/60))
     367                    else
     368                    ! Southern hemisphere
     369                      tau_pref_MGS(ig) = tauS + (taueq-tauS)*0.5 &
     370                             *(1+tanh((45+latitude(ig)*180./pi)*6/60))
     371                    endif
     372                  endif
     373
     374              ENDDO
     375            ENDDO
     376
     377          ELSE
     378!           Fixed dust
    322379
    323380!           expfactor=0.
    324            DO l=1,nlayer-1
    325              DO ig=1,ngrid
     381            topdust=30.0 ! km  (used to be 10.0 km) LK
     382
     383            DO l=1,nlayer-1
     384              DO ig=1,ngrid
     385
     386           
    326387!             Typical mixing ratio profile
    327388
     
    329390                 expfactor=max(exp(0.007*(1.-max(zp,1.))),1.e-3)
    330391
    331 !             Vertical scaling function
    332               aerosol(ig,l,iaer)= (pplev(ig,l)-pplev(ig,l+1)) &
    333                *expfactor
     392!               Vertical scaling function
     393                aerosol(ig,l,iaer)= (pplev(ig,l)-pplev(ig,l+1)) &
     394                 *expfactor
    334395
    335396
    336397             ENDDO
    337398           ENDDO
     399          ENDIF ! of if timedepdust
     400
    338401
    339402!          Rescaling each layer to reproduce the choosen (or assimilated)
     
    348411                ENDDO
    349412              ENDDO
     413   
     414            if (timedepdust) then
     415!             Dust opacity scaling
     416              tauscaling(:) = tau_pref_MGS(:) * pplev(:,1) / odpref
     417            else
     418              tauscaling(:) = 1
     419            endif
     420
    350421            DO l=1,nlayer-1
    351422               DO ig=1,ngrid
    352                   aerosol(ig,l,iaer) = max(1E-20, &
    353                           dusttau &
    354                        *  pplev(ig,1) / pplev(ig,1) &
     423                aerosol(ig,l,iaer) = max(1E-20, &
     424                          dusttau * tauscaling(ig) &
     425                       *  pplev(ig,1) / pplev(ig,1) & ! what is the use of this line ? (MM)
    355426                       *  aerosol(ig,l,iaer) &
    356427                       /  taudusttmp(ig))
     428               
    357429
    358430              ENDDO
    359431            ENDDO
     432           
     433            call writediagfi(ngrid,"taudust","Optical depth at pref","-",2, dusttau * tauscaling)
     434
    360435      end if ! If dust aerosol   
    361436
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r3654 r3922  
    55CONTAINS
    66
    7       subroutine callcorrk(ngrid,nlayer,pq,nq,qsurf,           &
     7      subroutine callcorrk(ngrid,nlayer,pq,nq,qsurf,zls,       &
    88          albedo,albedo_equivalent,emis,mu0,pplev,pplay,pt,    &
    99          tsurf,fract,dist_star,aerosol,muvar,                 &
     
    8080      INTEGER,INTENT(IN) :: nq                     ! Number of tracers.
    8181      REAL,INTENT(IN) :: qsurf(ngrid,nq)           ! Tracers on surface (kg.m-2).
     82      REAL,INTENT(IN) :: zls                       ! Stellar longitude (rad).
    8283      REAL,INTENT(IN) :: albedo(ngrid,L_NSPECTV)   ! Spectral Short Wavelengths Albedo. By MT2015
    8384      REAL,INTENT(IN) :: emis(ngrid)               ! Long Wave emissivity.
     
    554555
    555556      ! Get aerosol optical depths.
    556       call aeropacity(ngrid,nlayer,nq,pplay,pplev, pt,pq,aerosol,      &
     557      call aeropacity(ngrid,nlayer,nq,pplay,pplev,pt,pq,zls,aerosol,      &
    557558           reffrad,nueffrad,QREFvis3d,QREFir3d,                             &
    558559           tau_col,cloudfrac,totcloudfrac,clearsky)               
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r3701 r3922  
    121121      real,save :: topdustref
    122122      real,save :: dusttau
     123      logical,save :: timedepdust
    123124      real,save :: Fat1AU
    124125      real,save :: stelTbb
    125 !$OMP THREADPRIVATE(topdustref,dusttau,Fat1AU,stelTbb)
     126!$OMP THREADPRIVATE(topdustref,dusttau,timedepdust,Fat1AU,stelTbb)
    126127      real,save :: Tstrat
    127128      real,save :: tplanet
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r3893 r3922  
    723723     call getin_p("dusttau",dusttau)
    724724     if (is_master) write(*,*)trim(rname)//": dusttau = ",dusttau
     725     
     726     if (is_master) write(*,*)trim(rname)//": Use time-dependent dust ?:"
     727     timedepdust=.false. ! default value
     728     call getin_p("timedepdust",timedepdust)
     729     if (is_master) write(*,*)trim(rname)//": timedepdust = ",timedepdust
    725730
    726731     if (is_master) write(*,*)trim(rname)//": Radiatively active CO2 aerosols?"
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r3921 r3922  
    10581058               ! standard callcorrk
    10591059               clearsky=.false.
    1060                call callcorrk(ngrid,nlayer,pq,nq,qsurf,                           &
     1060               call callcorrk(ngrid,nlayer,pq,nq,qsurf,zls,                        &
    10611061                              albedo,albedo_equivalent,emis,mu0,pplev,pplay,pt,   &
    10621062                              tsurf,fract,dist_star,aerosol,muvar,                &
     
    10891089                  ! ---> PROBLEMS WITH ALLOCATED ARRAYS : temporary solution in callcorrk: do not deallocate if CLFvarying ...
    10901090                  clearsky=.true.
    1091                   call callcorrk(ngrid,nlayer,pq,nq,qsurf,                           &
     1091                  call callcorrk(ngrid,nlayer,pq,nq,qsurf,zls,                       &
    10921092                                 albedo,albedo_equivalent1,emis,mu0,pplev,pplay,pt,  &
    10931093                                 tsurf,fract,dist_star,aerosol,muvar,                &
Note: See TracChangeset for help on using the changeset viewer.