Changeset 2413 for trunk


Ignore:
Timestamp:
Sep 30, 2020, 5:15:08 PM (4 years ago)
Author:
emillour
Message:

Mars GCM:
Cleanup around "aeropacity" to prepare future evolutions; added module
dust_scaling_mod to handle computation of tauscaling.
EM

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

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2411 r2413  
    31513151madly skyrocket in the dusty season.
    31523152+ correction of a comment for abort_physic
     3153
     3154== 30/09/2020 == EM
     3155Cleanup around "aeropacity" to prepare future evolutions; added module
     3156dust_scaling_mod to handle computation of tauscaling.
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r2409 r2413  
    3535     &            iaer_topdust_doubleq
    3636      use dust_param_mod, only: odpref, freedust
     37      use dust_scaling_mod, only: compute_tauscaling
    3738       IMPLICIT NONE
    3839c=======================================================================
     
    8889      REAL, INTENT(IN) ::  pplev(ngrid,nlayer+1),pplay(ngrid,nlayer)
    8990      REAL, INTENT(IN) ::  pq(ngrid,nlayer,nq)
    90       REAL, INTENT(OUT) :: tauref(ngrid)
     91      REAL, INTENT(OUT) :: tauref(ngrid) ! prescribed or computed
     92                                         ! column dust opacity
    9193      REAL, INTENT(OUT) :: tau(ngrid,naerkind)
     94      REAL,INTENT(OUT) :: taucloudtes(ngrid)! Cloud opacity at infrared
     95                               !   reference wavelength using
     96                               !   Qabs instead of Qext
     97                               !   (direct comparison with TES)
    9298      REAL, INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
    93       REAL, INTENT(INOUT) ::  dsodust(ngrid,nlayer)
    94       REAL, INTENT(INOUT) ::  dsords(ngrid,nlayer) !dso of stormdust
    95       REAL, INTENT(INOUT) ::  dsotop(ngrid,nlayer) !dso of topdust 
     99      REAL, INTENT(OUT) ::  dsodust(ngrid,nlayer)
     100      REAL, INTENT(OUT) ::  dsords(ngrid,nlayer) !dso of stormdust
     101      REAL, INTENT(OUT) ::  dsotop(ngrid,nlayer) !dso of topdust 
    96102      REAL, INTENT(INOUT) :: reffrad(ngrid,nlayer,naerkind)
    97103      REAL, INTENT(IN) :: QREFvis3d(ngrid,nlayer,naerkind)
     
    122128c       for dust or water ice particles in the radiative transfer
    123129c       (see callradite.F for more information).
    124       REAL taudusttmp(ngrid)! Temporary dust opacity used before scaling
    125       REAL taubackdusttmp(ngrid)! Temporary background dust opacity used before scaling
    126       REAL taualldust(ngrid)! dust opacity all dust
    127       REAL taudust(ngrid)! dust opacity dust doubleq
    128       REAL taustormdust(ngrid)! dust opacity stormdust doubleq
    129       REAL taustormdusttmp(ngrid)! dust opacity stormdust doubleq before tauscaling
    130       REAL taudustvis(ngrid) ! Dust opacity after scaling
    131       REAL taudusttes(ngrid) ! Dust opacity at IR ref. wav. as
    132                                !   "seen" by the GCM.
    133130      REAL taucloudvis(ngrid)! Cloud opacity at visible
    134131                               !   reference wavelength
    135       REAL taucloudtes(ngrid)! Cloud opacity at infrared
    136                                !   reference wavelength using
    137                                !   Qabs instead of Qext
    138                                !   (direct comparison with TES)
    139132      REAL topdust0(ngrid)
    140133
     
    244237      END IF ! end of if firstcall
    245238
    246 c     Vertical column optical depth at "odpref" Pa
    247 c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     239! 1. Get prescribed tauref, Dust column optical depth at "odpref" Pa
     240!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    248241      IF(freedust) THEN
    249242         tauref(:) = 0. ! tauref is computed after, instead of being forced
     
    266259        tauS= 0.1 +(0.5-0.1)  *(cos(0.5*(ls-4.363)))**14
    267260        tauN = 0.1
    268 c          if (peri_day.eq.150) then
    269 c            tauS=0.1
    270 c            tauN=0.1 +(0.5-0.1)  *(cos(0.5*(ls+pi-4.363)))**14
    271 c            taueq= 0.2 +(0.5-0.2) *(cos(0.5*(ls+pi-4.363)))**14
    272 c           endif
    273261        do ig=1,ngrid
    274262          if (latitude(ig).ge.0) then
     
    283271        enddo ! of do ig=1,ngrid
    284272      ELSE IF (iaervar.eq.5) THEN   ! << Escalier Scenario>>
    285 c         tauref(1) = 0.2
    286 c         if ((ls.ge.210.*pi/180.).and.(ls.le.330.*pi/180.))
    287 c    &                              tauref(1) = 2.5
    288273        tauref(1) = 2.5
    289274        if ((ls.ge.30.*pi/180.).and.(ls.le.150.*pi/180.))
     
    307292      ENDIF
    308293
    309 c -----------------------------------------------------------------
    310 c Computing the opacity in each layer
    311 c -----------------------------------------------------------------
    312 
    313       DO iaer = 1, naerkind ! Loop on aerosol kind
     294! -----------------------------------------------------------------
     295! 2. Compute/set the opacity of each aerosol in each layer
     296! -----------------------------------------------------------------
     297
     298      DO iaer = 1, naerkind ! Loop on all aerosols
    314299c     --------------------------------------------
    315300        aerkind: SELECT CASE (name_iaer(iaer))
     
    488473                ENDDO
    489474             ENDDO
    490 !          ELSE ! else (CLFvarying)
    491 !             DO ig=1, ngrid
    492 !                DO l=1,nlayer-1 ! to stop the rad tran bug
    493 !                   CLFtot  = CLFfixval
    494 !                   aerosol(ig,l,iaer)=
    495 !     &                    aerosol(ig,l,iaer)/CLFtot
    496 !                   aerosol(ig,l,iaer) =
    497 !     &                    max(aerosol(ig,l,iaer),1.e-9)
    498 !                ENDDO
    499 !             ENDDO
    500475          ENDIF ! end (CLFvarying)             
    501476        ENDIF ! end (clearsky)
     
    607582      ENDDO ! iaer (loop on aerosol kind)
    608583
    609 c -----------------------------------------------------------------
    610 c Rescaling each layer to reproduce the choosen (or assimilated)
    611 c   dust extinction opacity at visible reference wavelength, which
    612 c   is originally scaled to an equivalent odpref Pa pressure surface.
    613 c -----------------------------------------------------------------
    614 
     584! 3. Specific treatments for the dust aerosols
    615585
    616586#ifdef DUSTSTORM
     
    753723#endif
    754724
    755       IF (freedust) THEN
    756           tauscaling(:) = 1.
    757 c        opacity obtained with stormdust
    758         IF (rdstorm) THEN
    759            taustormdusttmp(1:ngrid)=0.
    760            DO l=1,nlayer
    761              DO ig=1,ngrid
    762                 taustormdusttmp(ig) = taustormdusttmp(ig)+
    763      &            aerosol(ig,l,iaerdust(2))
    764              ENDDO
    765            ENDDO
    766            !opacity obtained with background dust only
    767            taubackdusttmp(1:ngrid)=0. 
    768            DO l=1,nlayer
    769              DO ig=1,ngrid
    770                 taubackdusttmp(ig) = taubackdusttmp(ig)+
    771      &           aerosol(ig,l,iaerdust(1))
    772              ENDDO
    773            ENDDO
    774         ENDIF !rdsstorm
    775       ELSE
    776 c       Temporary scaling factor
    777         taudusttmp(1:ngrid)=0.
    778         DO iaer=1,naerdust
    779           DO l=1,nlayer
    780             DO ig=1,ngrid
    781 c             Scaling factor
    782               taudusttmp(ig) = taudusttmp(ig) +
    783      &                         aerosol(ig,l,iaerdust(iaer))
    784             ENDDO
    785           ENDDO
    786         ENDDO
    787 
    788 c       Saved scaling factor
    789         DO ig=1,ngrid
    790             tauscaling(ig) = tauref(ig) *
    791      &                       pplev(ig,1) / odpref / taudusttmp(ig)
    792         ENDDO
    793 
    794       ENDIF ! IF (freedust)
    795 
    796 c     Opacity computation
    797       DO iaer=1,naerdust
    798         DO l=1,nlayer
    799           DO ig=1,ngrid
    800             aerosol(ig,l,iaerdust(iaer)) = max(1E-20,
    801      &                aerosol(ig,l,iaerdust(iaer))* tauscaling(ig))
    802           ENDDO
    803         ENDDO
    804       ENDDO
     725!
     726! 3.1. Compute "tauscaling", the dust rescaling coefficient and adjust
     727!      aerosol() dust opacities accordingly
     728      call compute_tauscaling(ngrid,nlayer,naerkind,naerdust,
     729     &                        zday,pplev,tauref,tauscaling,aerosol)
     730
     731! 3.2. Recompute tauref, the reference dust opacity, based on dust tracer
     732!      mixing ratios and their optical properties
    805733
    806734      IF (freedust) THEN
     
    819747      ENDIF
    820748#endif
    821 !              tauref(ig) = tauref(ig) +
    822 !     &                    aerosol(ig,l,iaerdust(iaer))
    823749c      MV19: tauref must ALWAYS contain the opacity of all dust tracers
    824750       IF (name_iaer(iaerdust(iaer)).eq."dust_doubleq") THEN
     
    846772        ENDDO
    847773        tauref(:) = tauref(:) * odpref / pplev(:,1)
    848       ENDIF
    849 
    850 c -----------------------------------------------------------------
    851 c Column integrated visible optical depth in each point
    852 c -----------------------------------------------------------------
     774      ENDIF ! of IF (freedust)
     775
     776! -----------------------------------------------------------------
     777! 4. Total integrated visible optical depth of aerosols in each column
     778! -----------------------------------------------------------------
    853779      DO iaer=1,naerkind
    854780        do l=1,nlayer
     
    859785      ENDDO
    860786
    861 c     for diagnostics: opacity for all dust scatterers stormdust included
    862       taualldust(1:ngrid)=0.
    863       DO iaer=1,naerdust
    864         DO l=1,nlayer
    865           DO ig=1,ngrid
    866             taualldust(ig) = taualldust(ig) +
    867      &                         aerosol(ig,l,iaerdust(iaer))
    868           ENDDO
    869         ENDDO
    870       ENDDO
    871      
    872       IF (rdstorm) THEN
    873  
    874 c     for diagnostics: opacity for dust in background only 
    875        taudust(1:ngrid)=0.
    876         DO l=1,nlayer
    877          DO ig=1,ngrid
    878            taudust(ig) = taudust(ig) +
    879      &                       aerosol(ig,l,iaer_dust_doubleq)
    880          ENDDO
    881         ENDDO
    882 
    883 c     for diagnostics: opacity for dust in storm only 
    884        taustormdust(1:ngrid)=0.
    885         DO l=1,nlayer
    886          DO ig=1,ngrid
    887            taustormdust(ig) = taustormdust(ig) +
    888      &                       aerosol(ig,l,iaer_stormdust_doubleq)
    889          ENDDO
    890         ENDDO
    891  
    892       ENDIF
    893      
    894787
    895788#ifdef DUSTSTORM
     
    899792#endif
    900793
     794!
     795! 5. Adapt aerosol() for the radiative transfer (i.e. account for
     796!    cases when it refers to a fraction of the global mesh)
     797!
    901798
    902799c -----------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r2411 r2413  
    4646      use co2condens_mod, only: scavco2cond
    4747      use dust_param_mod, only: dustbin, doubleq, submicron, active,
    48      &                          lifting, freedust, callddevil
     48     &                          lifting, freedust, callddevil,
     49     &                          tauscaling_mode
    4950      use aeropacity_mod, only: iddist, topdustref
    5051      IMPLICIT NONE
     
    428429     &          "freedust option requires doubleq",1)
    429430         endif
     431
     432! dust rescaling mode (if any)
     433         if (freedust) then
     434           tauscaling_mode=0
     435         else
     436           tauscaling_mode=1 ! GCMv5.3 style
     437         endif
     438         call getin_p("tauscaling_mode",tauscaling_mode)
     439         write(*,*) "tauscaling_mode=",tauscaling_mode
     440
    430441#ifndef MESOSCALE
    431442         ! this test is valid in GCM case
  • trunk/LMDZ.MARS/libf/phymars/dust_param_mod.F90

    r2409 r2413  
    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
    1719
    1820contains
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2409 r2413  
    418418      REAL rdsqdust(ngrid,nlayer) ! true q stormdust (kg/kg)
    419419      REAL wspeed(ngrid,nlayer+1) ! vertical velocity stormdust tracer
    420       REAL dsodust(ngrid,nlayer)
    421       REAL dsords(ngrid,nlayer)
    422       REAL dsotop(ngrid,nlayer)
     420      REAL dsodust(ngrid,nlayer) ! density scaled opacity for background dust
     421      REAL dsords(ngrid,nlayer) ! density scaled opacity for stormdust
     422      REAL dsotop(ngrid,nlayer) ! density scaled opacity for topdust
    423423      REAL wtop(ngrid,nlayer+1) ! vertical velocity topdust tracer
    424424
Note: See TracChangeset for help on using the changeset viewer.