Changeset 2417 for trunk


Ignore:
Timestamp:
Oct 16, 2020, 9:40:05 AM (4 years ago)
Author:
emillour
Message:

Mars GCM:
Add a new scheme to handle the dust and its radiative impact. Triggered using
a new flag dustscaling_mode=2 (dustscaling_mod=0: no rescaling at all, and
dustscaling_mode=1: full rescaling using tauscaling, GCMv5.3 style). Rescaling
is then only done on the radiative impact (see dust_scaling_mod.F90) of dust.
Moreover the scaling factor "dust_rad_adjust" is evaluated using the target dust
scenario opacity for the next sol and left to evolve linearly until then to not
impose the diurnal evolution of dust.
In practice, main changes or additions in the code are:

  • renamed flag "tauscaling_mode" as "dustscaling_mode"
  • moved parameter "t_scenario_sol" to "dust_param_mod"
  • adapted "compute_dustscaling" routine in "dust_scaling_mod"
  • added module "dust_rad_adjust_mod"
  • 2D fields "dust_rad_adjust_prev" and "dust_rad_adjust_next" required to compute coefficient "dust_rad_adjust" need to be stored in (re)startfi files

EM

Location:
trunk/LMDZ.MARS
Files:
1 added
13 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2416 r2417  
    31703170+ Resolved Ticket #61 : add comments in the code and in the output file to make the program more
    31713171transparent for the users
     3172
     3173== 16/10/2020 == EM
     3174Add a new scheme to handle the dust and its radiative impact. Triggered using
     3175a new flag dustscaling_mode=2 (dustscaling_mod=0: no rescaling at all, and
     3176dustscaling_mode=1: full rescaling using tauscaling, GCMv5.3 style). Rescaling
     3177is then only done on the radiative impact (see dust_scaling_mod.F90) of dust.
     3178Moreover the scaling factor "dust_rad_adjust" is evaluated using the target dust
     3179scenario opacity for the next sol and left to evolve linearly until then to not
     3180impose the diurnal evolution of dust.
     3181In practice, main changes or additions in the code are:
     3182- renamed flag "tauscaling_mode" as "dustscaling_mode"
     3183- moved parameter "t_scenario_sol" to "dust_param_mod"
     3184- adapted "compute_dustscaling" routine in "dust_scaling_mod"
     3185- added module "dust_rad_adjust_mod"
     3186- 2D fields "dust_rad_adjust_prev" and "dust_rad_adjust_next" required to
     3187  compute coefficient "dust_rad_adjust" need to be stored in (re)startfi files
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r2415 r2417  
    1010
    1111      SUBROUTINE aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    12      &    pq,tauscaling,tau_pref_scenario,tau_pref_gcm,
     12     &    pq,tauscaling,dust_rad_adjust,tau_pref_scenario,tau_pref_gcm,
    1313     &    tau,taucloudtes,aerosol,dsodust,reffrad,
    1414     &    QREFvis3d,QREFir3d,omegaREFir3d,
     
    3636     &            iaer_topdust_doubleq
    3737      use dust_param_mod, only: odpref, freedust
    38       use dust_scaling_mod, only: compute_tauscaling
     38      use dust_scaling_mod, only: compute_dustscaling
    3939       IMPLICIT NONE
    4040c=======================================================================
     
    105105                             ! topdust, false to compute RT in the topdust
    106106      REAL, INTENT(IN) :: alpha_hmons(ngrid)
    107       REAL, INTENT(OUT) ::  tauscaling(ngrid) ! Scaling factor for qdust and Ndust
     107      REAL,INTENT(OUT) :: tauscaling(ngrid) ! Scaling factor for qdust and Ndust
     108      REAL,INTENT(OUT) :: dust_rad_adjust(ngrid) ! Radiative adjustment
     109                          ! factor for dust
    108110      REAL,INTENT(IN) :: totcloudfrac(ngrid) ! total water ice cloud fraction
    109111      LOGICAL,INTENT(IN) :: clearsky ! true to compute RT without water ice clouds
     
    720722
    721723!
    722 ! 3.1. Compute "tauscaling", the dust rescaling coefficient and adjust
    723 !      aerosol() dust opacities accordingly
    724       call compute_tauscaling(ngrid,nlayer,naerkind,naerdust,zday,pplev,
    725      &                        tau_pref_scenario,tauscaling,aerosol)
     724! 3.1. Compute "tauscaling" and "dust_rad_adjust", the dust rescaling
     725!      coefficients and adjust aerosol() dust opacities accordingly
     726      call compute_dustscaling(ngrid,nlayer,naerkind,naerdust,zday,pplev
     727     &                         ,tau_pref_scenario,tauscaling,
     728     &                          dust_rad_adjust,aerosol)
    726729
    727730! 3.2. Recompute tau_pref_gcm, the reference dust opacity, based on dust tracer
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r2415 r2417  
    99     $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,
    1010     $     fluxtop_sw,tau_pref_scenario,tau_pref_gcm,
    11      &     tau,aerosol,dsodust,tauscaling,
     11     &     tau,aerosol,dsodust,tauscaling,dust_rad_adjust,
    1212     $     taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust,
    1313     $     totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,
     
    177177      REAL,INTENT(INOUT) :: tauscaling(ngrid) ! Conversion factor for
    178178                               ! qdust and Ndust
     179      REAL,INTENT(OUT) :: dust_rad_adjust(ngrid) ! Radiative adjustment
     180                          ! factor for dust
    179181      REAL,INTENT(IN) :: albedo(ngrid,2),emis(ngrid)
    180182      REAL,INTENT(IN) :: ls,zday
     
    426428c     Computing aerosol optical depth in each layer:
    427429      CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    428      &    pq,tauscaling,tau_pref_scenario,tau_pref_gcm,
     430     &    pq,tauscaling,dust_rad_adjust,tau_pref_scenario,tau_pref_gcm,
    429431     &    tau,taucloudtes,aerosol,dsodust,reffrad,
    430432     &    QREFvis3d,QREFir3d,omegaREFir3d,
  • trunk/LMDZ.MARS/libf/phymars/compute_dtau_mod.F90

    r2415 r2417  
    55        REAL,SAVE :: ti_injection_sol ! time of beginning injection
    66        REAL,SAVE :: tf_injection_sol ! time of end injection
    7         REAL,PARAMETER :: t_scenario_sol=14/24. ! time of day at which
    8                           ! tau_pref_scenario is deemed exact
    97
    108        REAL,SAVE,ALLOCATABLE :: dtau(:) ! Dust opacity difference (at 610Pa)
     
    2220        USE tracer_mod, only: alpha_lift,igcm_dust_mass,igcm_dust_number
    2321        USE dimradmars_mod, only: tauvis
    24         USE dust_param_mod, only: odpref
     22        USE dust_param_mod, only: odpref, t_scenario_sol
    2523       
    2624        IMPLICIT NONE
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r2413 r2417  
    4747      use dust_param_mod, only: dustbin, doubleq, submicron, active,
    4848     &                          lifting, freedust, callddevil,
    49      &                          tauscaling_mode
     49     &                          dustscaling_mode
    5050      use aeropacity_mod, only: iddist, topdustref
    5151      IMPLICIT NONE
     
    432432! dust rescaling mode (if any)
    433433         if (freedust) then
    434            tauscaling_mode=0
     434           dustscaling_mode=0
    435435         else
    436            tauscaling_mode=1 ! GCMv5.3 style
    437          endif
    438          call getin_p("tauscaling_mode",tauscaling_mode)
    439          write(*,*) "tauscaling_mode=",tauscaling_mode
     436           dustscaling_mode=1 ! GCMv5.3 style
     437         endif
     438         call getin_p("dustscaling_mode",dustscaling_mode)
     439         write(*,*) "dustscaling_mode=",dustscaling_mode
    440440
    441441#ifndef MESOSCALE
  • trunk/LMDZ.MARS/libf/phymars/dust_param_mod.F90

    r2415 r2417  
    1515 
    1616  REAL,SAVE,ALLOCATABLE :: tauscaling(:)   ! Convertion factor for qdust and Ndust
    17   INTEGER,SAVE :: tauscaling_mode ! =0, no rescaling (freedust)
    18                                   ! =1, prescribed scaling GCM5.3 style
     17  INTEGER,SAVE :: dustscaling_mode ! dust scaling modes
     18                  ! =0, no rescaling (freedust)
     19                  ! =1, prescribed scaling GCM5.3 style (using tauscaling)
     20                  ! =2, only radiative scaling (using dust_rad_adjust)
     21  REAL,SAVE,ALLOCATABLE :: dust_rad_adjust(:) ! radiative scaling for dust
     22  REAL,PARAMETER :: t_scenario_sol=14/24. ! time of day (sol) at which
     23                    ! tau_pref_scenario is deemed exact
    1924
    2025contains
     
    2530 
    2631    allocate(tauscaling(ngrid))
     32    allocate(dust_rad_adjust(ngrid))
    2733 
    2834  end subroutine ini_dust_param_mod
     
    3238   
    3339    if (allocated(tauscaling))  deallocate(tauscaling)
     40    if (allocated(dust_rad_adjust)) deallocate(dust_rad_adjust)
    3441
    3542  end subroutine end_dust_param_mod
  • trunk/LMDZ.MARS/libf/phymars/dust_scaling_mod.F90

    r2415 r2417  
    55contains
    66
    7   subroutine compute_tauscaling(ngrid,nlayer,naerkind,naerdust, &
    8                                 zday,pplev, &
    9                                 tau_pref_scenario,tauscaling,aerosol)
     7  subroutine compute_dustscaling(ngrid,nlayer,naerkind,naerdust, &
     8                                 zday,pplev, &
     9                                 tau_pref_scenario,tauscaling, &
     10                                 dust_rad_adjust,aerosol)
    1011   
    11     use dust_param_mod, only: tauscaling_mode, odpref
     12    use dust_param_mod, only: dustscaling_mode, odpref
     13    use dust_rad_adjust_mod, only: compute_dust_rad_adjust
    1214    use dimradmars_mod, only: iaerdust ! dust aerosol indexes
    1315   
     
    2325                       ! opacity column at odpref reference pressure
    2426    real,intent(out) :: tauscaling(ngrid) ! dust scaling factor
     27    real,intent(out) :: dust_rad_adjust(ngrid) ! Radiative adjustment
     28                          ! factor for dust
    2529    real,intent(inout) :: aerosol(ngrid,nlayer,naerkind) ! opacities
    2630   
    2731    integer :: ig, l , iaer
    2832    real :: taudust(ngrid)
    29    
     33
    3034  ! 1. compute/set tauscaling
    3135
    32     if (tauscaling_mode == 0) then
    33       ! simple "freedust" case, no rescaling, ever
     36    if (dustscaling_mode /= 1) then
     37      ! simple "freedust" case, no effective rescaling using tauscaling, ever
    3438      tauscaling(:) = 1
    3539    endif
    3640   
    37     if (tauscaling_mode == 1) then
    38       ! GCM v5.3 style: tauscaling is computed so that
    39       ! aerosol() opacities correspond to the prescribed tau_pref_scenario()
    40      
    41       ! 1. compute dust column opacity using aerosol() dusts
     41    if (dustscaling_mode == 1) then
     42      ! Compute dust column opacity using aerosol() dusts
    4243      taudust(:) = 0
    4344      do iaer=1,naerdust ! loop on all dust aerosols
     
    4849        enddo
    4950      enddo
    50      
    51       ! 2. compute the scaling factor
    52       tauscaling(:)=tau_pref_scenario(:)*pplev(:,1)/odpref/taudust(:)
    53     endif ! of if (tauscaling_mode == 1)
    54    
    55   ! 2. dust opacities rescaling
    56     do iaer=1,naerdust
     51
     52    elseif (dustscaling_mode == 2) then
     53      ! Compute dust column opacity using only background dust
     54      taudust(:) = 0
    5755      do l=1,nlayer
    5856        do ig=1,ngrid
     57            taudust(ig)=taudust(ig)+aerosol(ig,l,iaerdust(1))
     58        enddo
     59      enddo
     60
     61    endif ! of if (dustscaling_mode == 1) elseif (dustscaling_mode == 2)
     62     
     63  ! 2. compute the scaling factors (tauscaling or dust_rad_adjust)
     64    if (dustscaling_mode==1) then
     65      ! GCM v5.3 style: tauscaling is computed so that
     66      ! aerosol() opacities correspond to the prescribed tau_pref_scenario()
     67      tauscaling(:)=tau_pref_scenario(:)*pplev(:,1)/odpref/taudust(:)
     68    elseif (dustscaling_mode==2) then
     69      ! GCM v6 style, compute dust_rad_adjust
     70      call compute_dust_rad_adjust(ngrid,nlayer,zday,pplev, &
     71                                   taudust,dust_rad_adjust)
     72    endif
     73
     74  ! 3. Apply dust aerosol opacities rescaling
     75    if (dustscaling_mode <=1) then
     76      do iaer=1,naerdust
     77        do l=1,nlayer
     78          do ig=1,ngrid
    5979            aerosol(ig,l,iaerdust(iaer)) = max(1E-20, &
    6080                      aerosol(ig,l,iaerdust(iaer))* tauscaling(ig))
     81          enddo
    6182        enddo
    6283      enddo
    63     enddo
    64 
    65   end subroutine compute_tauscaling
     84    else ! duscaling_mode==2, use dust_rad_adjust
     85      do iaer=1,naerdust
     86        do l=1,nlayer
     87          do ig=1,ngrid
     88            aerosol(ig,l,iaerdust(iaer)) = max(1E-20, &
     89                      aerosol(ig,l,iaerdust(iaer))*dust_rad_adjust(ig))
     90          enddo
     91        enddo
     92      enddo
     93    endif
     94  end subroutine compute_dustscaling
    6695
    6796end module dust_scaling_mod
  • trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90

    r2378 r2417  
    1818  use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd
    1919  use compute_dtau_mod, only: dtau
    20 
     20  use dust_rad_adjust_mod, only: dust_rad_adjust_prev,dust_rad_adjust_next
     21  use dust_param_mod, only: dustscaling_mode
    2122  USE ioipsl_getin_p_mod, ONLY : getin_p
    2223
     
    411412            minval(tauscaling), maxval(tauscaling)
    412413
     414! dust_rad_adjust_* for radiative rescaling of dust
     415if (dustscaling_mode==2) then
     416 if (startphy_file) then
     417   call get_field("dust_rad_adjust_prev",dust_rad_adjust_prev,found,indextime)
     418   if (.not.found) then
     419     write(*,*) "phyetat0: <dust_rad_adjust_prev> not in file; set to 1"
     420     dust_rad_adjust_prev(:) = 1
     421   endif
     422   call get_field("dust_rad_adjust_next",dust_rad_adjust_next,found,indextime)
     423   if (.not.found) then
     424     write(*,*) "phyetat0: <dust_rad_adjust_next> not in file; set to 1"
     425     dust_rad_adjust_next(:) = 1
     426   endif
     427 else
     428   dust_rad_adjust_prev(:)= 0
     429   dust_rad_adjust_next(:)= 0
     430 endif ! if (startphy_file)
     431 write(*,*) "phyetat0: radiative scaling coeff <dust_rad_adjust_prev> range:", &
     432            minval(dust_rad_adjust_prev), maxval(dust_rad_adjust_prev)
     433 write(*,*) "phyetat0: radiative scaling coeff <dust_rad_adjust_next> range:", &
     434            minval(dust_rad_adjust_next), maxval(dust_rad_adjust_next)
     435endif ! of if (dustscaling_mode==2)
    413436
    414437! dtau: opacity difference between GCM and dust scenario
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r2312 r2417  
    157157  use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd
    158158  use compute_dtau_mod, only: dtau
     159  use dust_rad_adjust_mod, only: dust_rad_adjust_prev,dust_rad_adjust_next
     160  use dust_param_mod, only: dustscaling_mode
    159161
    160162  implicit none
     
    229231  call put_field("tauscaling","dust conversion factor",tauscaling,time)
    230232
     233  ! Radiative scaling coefficients
     234  if (dustscaling_mode==2) then
     235    call put_field("dust_rad_adjust_prev", &
     236                   "radiative dust adjustement factor prev. sol", &
     237                   dust_rad_adjust_prev,time)
     238    call put_field("dust_rad_adjust_next", &
     239                   "radiative dust adjustement factor next sol", &
     240                   dust_rad_adjust_next,time)
     241  endif
     242 
    231243  if (dustinjection.gt.0) then
    232244    call put_field("dtau","dust opacity difference between GCM and scenario",&
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r2409 r2417  
    6262      use dust_param_mod, only: ini_dust_param_mod, &
    6363                                end_dust_param_mod
    64 
     64      use dust_rad_adjust_mod, only: ini_dust_rad_adjust_mod, &
     65                                     end_dust_rad_adjust_mod
    6566      IMPLICIT NONE
    6667     
     
    161162      call end_dust_param_mod
    162163      call ini_dust_param_mod(ngrid)
     164     
     165      ! allocate arrays in "dust_rad_adjust_mod"
     166      call end_dust_rad_adjust_mod
     167      call ini_dust_rad_adjust_mod(ngrid)
    163168
    164169      END SUBROUTINE phys_state_var_init
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2415 r2417  
    5959     &                          iaer_stormdust_doubleq
    6060      use dust_param_mod, only: doubleq, lifting, callddevil,
    61      &                          tauscaling, odpref, dustbin
     61     &                          tauscaling, odpref, dustbin,
     62     &                          dustscaling_mode, dust_rad_adjust
    6263      use turb_mod, only: q2, wstar, ustar, sensibFlux,
    6364     &                    zmax_th, hfmax_th, turb_resolved
     
    931932     &     zdtlw,zdtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,
    932933     &     fluxtop_sw,tau_pref_scenario,tau_pref_gcm,
    933      &     tau,aerosol,dsodust,tauscaling,
     934     &     tau,aerosol,dsodust,tauscaling,dust_rad_adjust,
    934935     &     taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust,
    935936     &     totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,
     
    948949     &              fluxsurf_swclf,fluxtop_lwclf,fluxtop_swclf,
    949950     &              tau_pref_scenario,tau_pref_gcm,
    950      &              tau,aerosol,dsodust,tauscaling,taucloudtesclf,rdust,
     951     &              tau,aerosol,dsodust,tauscaling,dust_rad_adjust,
     952     &              taucloudtesclf,rdust,
    951953     &              rice,nuice,co2ice,rstormdust,rtopdust,totstormfract,
    952954     &              clearatm,dsords,dsotop,alpha_hmons,nohmons,
     
    11371139     &                      clearatm,icount,zday,zls,
    11381140     &                      tsurf,igout,totstormfract,
    1139      &                      tauscaling,
     1141     &                      tauscaling,dust_rad_adjust,
    11401142c               input sub-grid scale cloud
    11411143     &                      clearsky,totcloudfrac,
     
    12041206     &                zzlay,zdtsw,zdtlw,
    12051207     &                icount,zday,zls,tsurf,igout,aerosol,
    1206      &                tauscaling,totstormfract,clearatm,
     1208     &                tauscaling,dust_rad_adjust,
     1209     &                totstormfract,clearatm,
    12071210     &                clearsky,totcloudfrac,
    12081211     &                nohmons,hsummit,
     
    28532856        call WRITEDIAGFI(ngrid,'lw_htrt','lw heat. rate',
    28542857     &                   'w.m-2',3,zdtlw)
    2855  
     2858        call writediagfi(ngrid,"local_time","Local time",
     2859     &                   'sol',2,local_time)
    28562860            if (.not.activice) then
    28572861               CALL WRITEDIAGFI(ngrid,'tauTESap',
     
    32323236             end select
    32333237           endif ! (slpwind)
     3238
     3239           if (dustscaling_mode==2) then
     3240             call writediagfi(ngrid,"dust_rad_adjust",
     3241     &            "radiative adjustment coefficient for dust",
     3242     &                        "",2,dust_rad_adjust)
     3243           endif
    32343244
    32353245           if (scavenging) then
  • trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90

    r2415 r2417  
    2424                                 clearatm,icount,zday,zls,             &
    2525                                 tsurf,igout,totstormfract,            &
    26                                  tauscaling,                           &
     26                                 tauscaling,dust_rad_adjust,           &
    2727!             input sub-grid scale cloud
    2828                                 clearsky,totcloudfrac,                &
     
    7777      REAL, INTENT(IN) :: totstormfract(ngrid)
    7878      REAL, INTENT(INOUT) :: tauscaling(ngrid)
     79      REAL,INTENT(OUT) :: dust_rad_adjust(ngrid)
    7980     
    8081!     sbgrid scale water ice clouds
     
    249250                 zdtlw1,zdtsw1,fluxsurf_lw1,fluxsurf_sw1,fluxtop_lw1,     &
    250251                 fluxtop_sw1,tau_pref_scenario,tau_pref_gcm, &
    251                  tau,aerosol,dsodust,tauscaling,       &
     252                 tau,aerosol,dsodust,tauscaling,dust_rad_adjust,       &
    252253                 taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust, &
    253254                 totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,&
  • trunk/LMDZ.MARS/libf/phymars/topmons_mod.F90

    r2415 r2417  
    2424!             input for radiative transfer
    2525                                 icount,zday,zls,tsurf,igout,aerosol,  &
    26                                  tauscaling,                           &
     26                                 tauscaling,dust_rad_adjust,           &
    2727!             input sub-grid scale rocket dust storm
    2828                                 totstormfract,clearatm,               &
     
    7676      INTEGER, INTENT(IN) :: igout
    7777      REAL, INTENT(INOUT) :: tauscaling(ngrid)
     78      REAL,INTENT(OUT) :: dust_rad_adjust(ngrid)
    7879!     input sub-grid scale rocket dust storm
    7980      LOGICAL, INTENT(IN) :: clearatm
     
    275276                 zdtlw1,zdtsw1,fluxsurf_lw1,fluxsurf_sw1,fluxtop_lw1,  &
    276277                 fluxtop_sw1,tau_pref_scenario,tau_pref_gcm, &
    277                  tau,aerosol,dsodust,tauscaling,    &
     278                 tau,aerosol,dsodust,tauscaling,dust_rad_adjust,    &
    278279                 taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust, &
    279280                 totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,&
Note: See TracChangeset for help on using the changeset viewer.