Ignore:
Timestamp:
Apr 26, 2020, 7:45:46 PM (5 years ago)
Author:
jvatant
Message:

Add a generic n-layer aerosol scheme to replace the former buggy 2-layer scheme as well as the hard-coded NH3 cloud.

It can be called using 'aeronlay=.true.' in callphys.def, and set the number of layers (up to 4) with 'nlayaero'.
Then, the following parameters are read as arrays of size nlayaero in callphys.def (separated by blank space)


*aeronlay_tauref (Optical depth of aerosol layer at ref wavelenght)
*aeronlay_lamref (Ref wavelenght (m))
*aeronlay_choice (Choice for vertical profile - 1:tau follows atm scale height btwn top and bottom - 2:tau follows it own scale height)
*aeronlay_pbot (Bottom pressure (Pa))
*aeronlay_ptop (Top pressure (Pa) - useful only if choice=1)
*aeronlay_sclhght (Ratio of aerosol layer scale height / atmospheric scale height - useful only if choice=2 )
*aeronlay_size (Particle size (m))
*optprop_aeronlay_vis File for VIS opt properties.
*optprop_aeronlay_ir File for IR opt properties.

+Extra info :

+ In addition of solving the bug from 2-layer it enables different optical properties.
+ The former scheme are left for retrocompatibility (for now) but you should use the new one.
+ See aeropacity.F90 for the calculations

+ Each layer can have different optical properties, size of particle ...
+ You have different choices for vertical profile of the aerosol layers :

  • aeronlay_choice = 1 : Layer tau is spread between ptop and pbot following atm scale height.
  • aeronlay_choice = 2 : Layer tau follows its own scale height above cloud deck (pbot).

In this case ptop is dummy and sclhght gives the ratio H_cl/H_atm.

+ The reference wavelenght for input optical depth is now read as input (aeronlay_lamref)
+ Following the last point some comment is added in suaer_corrk about the 'not-really-dummy'ness of IR lamref..

File:
1 edited

Legend:

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

    r2254 r2297  
    1111                pres_bottom_tropo,pres_top_tropo,obs_tau_col_tropo,     &
    1212                pres_bottom_strato,pres_top_strato,obs_tau_col_strato,  &
    13                 tau_nh3_cloud, pres_nh3_cloud
     13                tau_nh3_cloud, pres_nh3_cloud,                          &
     14                nlayaero, aeronlay_tauref, aeronlay_choice,             &
     15                aeronlay_pbot, aeronlay_ptop, aeronlay_sclhght
    1416                 
    1517       implicit none
     
    2729!     update J.-B. Madeleine (2008)
    2830!     dust removal, simplification by Robin Wordsworth (2009)
     31!     Generic n-layer aerosol - J. Vatant d'Ollone (2020)
    2932!
    3033!     Input
     
    6265      logical,intent(in) :: clearsky
    6366
    64       real aerosol0, obs_tau_col_aurora, pm, pente_cloud
    65      
     67      real aerosol0, obs_tau_col_aurora, pm
     68      real pcloud_deck, cloud_slope
     69
    6670      real dp_strato(ngrid)
    6771      real dp_tropo(ngrid)
    68 
    69       INTEGER l,ig,iq,iaer
     72      real dp_layer(ngrid)
     73
     74      INTEGER l,ig,iq,iaer,ia
    7075
    7176      LOGICAL,SAVE :: firstcall=.true.
     
    129134        if (iaero_nh3.ne.0) then
    130135          print*,'iaero_nh3= ',iaero_nh3
     136        endif
     137        if (iaero_nlay(1).ne.0) then
     138          print*,'iaero_nlay= ',iaero_nlay(:)
    131139        endif
    132140        if (iaero_aurora.ne.0) then
     
    375383!    Two-layer aerosols (unknown composition)
    376384!    S. Guerlet (2013) - Modif by J. Vatant d'Ollone (2020)
     385!   
     386!    This scheme is deprecated and left for retrocompatibility
     387!    You should use the n-layer scheme below !
     388!
    377389!==================================================================
    378390
     
    435447                 aerosol(ig,l,iaer) = obs_tau_col_strato*aerosol(ig,l,iaer)/dp_strato(ig)
    436448               ENDIF
    437                write(*,*), aerosol(ig,l,iaer)
    438449            ENDDO
    439450         ENDDO
     
    445456!    Saturn/Jupiter ammonia cloud = thin cloud (scale height 0.2 hard coded...)
    446457!    S. Guerlet (2013)
     458!    JVO 20 : You should now use the generic n-layer scheme below
    447459!==================================================================
    448460
     
    461473
    462474             ELSEIF (pplev(ig,l) .le. pres_nh3_cloud ) THEN
    463              pente_cloud=5. !!(hard-coded, correspond to scale height 0.2)
    464              aerosol(ig,l,iaer) = ((pplev(ig,l)/pres_nh3_cloud)**(pente_cloud))*tau_nh3_cloud
     475             cloud_slope=5. !!(hard-coded, correspond to scale height 0.2)
     476             aerosol(ig,l,iaer) = ((pplev(ig,l)/pres_nh3_cloud)**(cloud_slope))*tau_nh3_cloud
    465477
    466478             ENDIF
     
    470482         
    471483!       3. Re-normalize to observed total column
    472          tau_col(:)=0.0
     484         dp_layer(:)=0.0
    473485         DO l=1,nlayer
    474486          DO ig=1,ngrid
    475                tau_col(ig) = tau_col(ig) &
     487               dp_layer(ig) = dp_layer(ig) &
    476488                     + aerosol(ig,l,iaer)/tau_nh3_cloud
    477489            ENDDO
     
    480492         DO ig=1,ngrid
    481493           DO l=1,nlayer-1
    482                 aerosol(ig,l,iaer)=aerosol(ig,l,iaer)/tau_col(ig)
     494                aerosol(ig,l,iaer)=aerosol(ig,l,iaer)/dp_layer(ig)
    483495           ENDDO
    484496         ENDDO
    485497
    486498     end if ! if NH3 cloud 
     499
     500!=========================================================================================================
     501!    Generic N-layers aerosols/clouds
     502!    Author : J. Vatant d'Ollone (2020)
     503!   
     504!    Purpose: Replaces and extents the former buggy 2-layer scheme as well as hard-coded NH3 cloud
     505!   
     506!    + Each layer can have different optical properties, size of particle ...
     507!    + Enables up to n=4 layers as we apparently cannot run with more scatterers (could be worth checking...)
     508!    + You have different choices for vertical profile of the aerosol layers :
     509!           * aeronlay_choice = 1 : Layer tau is spread between ptop and pbot following atm scale height.
     510!           * aeronlay_choice = 2 : Layer tau follows its own scale height above cloud deck (pbot).
     511!                                   In this case ptop is dummy and sclhght gives the ratio H_cl/H_atm.
     512!           * aeronlay_choice = ... feel free to add more cases  !
     513!    + Layers can overlap if needed (if you want a 'transition layer' as in the 2-scheme, just add it)
     514!
     515!=========================================================================================================
     516
     517      if (iaero_nlay(1) .ne.0) then
     518
     519        DO ia=1,nlayaero
     520           iaer=iaero_nlay(ia)
     521
     522!          a. Initialization
     523           aerosol(1:ngrid,1:nlayer,iaer)=0.D0
     524
     525!          b. Opacity calculation
     526           
     527           ! Case 1 : Follows atmospheric scale height between boundaries pressures
     528           ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     529           IF (aeronlay_choice(ia).eq.1) THEN
     530
     531             dp_layer(:)=0.D0
     532             DO ig=1,ngrid
     533               DO l=1,nlayer-1
     534                 !! i. Opacity follows scale height
     535                 IF ( pplev(ig,l).le.aeronlay_pbot(ia)   .AND.          &
     536                      pplev(ig,l).ge.aeronlay_ptop(ia) ) THEN
     537                   aerosol(ig,l,iaer) = ( pplev(ig,l) - pplev(ig,l+1) )
     538                   dp_layer(ig) = dp_layer(ig) + aerosol(ig,l,iaer)
     539                 !! ii. Outside aerosol layer boundaries: no aerosols
     540                 ELSE
     541                   aerosol(ig,l,iaer) = 0.D0
     542                 ENDIF
     543               ENDDO
     544             ENDDO
     545             ! iii. Re-normalize to required total opacity
     546             DO ig=1,ngrid
     547               DO l=1,nlayer-1
     548                 IF ( pplev(ig,l).le.aeronlay_pbot(ia)   .AND.          &
     549                      pplev(ig,l).ge.aeronlay_ptop(ia) ) THEN
     550                  aerosol(ig,l,iaer) = aerosol(ig,l,iaer) / dp_layer(ig) &
     551                                     * aeronlay_tauref(ia)
     552                 ENDIF
     553               ENDDO
     554             ENDDO
     555
     556           ! Case 2 : Follows input scale height
     557           ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     558           ELSE IF (aeronlay_choice(ia).eq.2) THEN
     559           
     560             cloud_slope  = 1.D0/aeronlay_sclhght(ia)
     561             pcloud_deck  = aeronlay_pbot(ia)
     562             dp_layer(:)  = 0.D0
     563
     564             DO ig=1,ngrid
     565               DO l=1,nlayer-1
     566                 !! i. Below cloud layer: no opacity
     567                 IF (pplev(ig,l) .gt. pcloud_deck) THEN
     568                   aerosol(ig,l,iaer) = 0.D0           
     569                 !! ii. Follows scale height above cloud deck
     570                 ELSEIF (pplev(ig,l) .le. pcloud_deck) THEN
     571                   aerosol(ig,l,iaer) = ((pplev(ig,l)/pcloud_deck)**(cloud_slope))
     572                   dp_layer(ig) = dp_layer(ig) + aerosol(ig,l,iaer)
     573                 ENDIF
     574               ENDDO
     575             ENDDO
     576             ! iii. Re-normalize to required total opacity
     577             DO ig=1,ngrid
     578               DO l=1,nlayer-1
     579                 IF (pplev(ig,l) .le. pcloud_deck) THEN
     580                  aerosol(ig,l,iaer) = aerosol(ig,l,iaer) / dp_layer(ig) &
     581                                     * aeronlay_tauref(ia)
     582                 ENDIF
     583               ENDDO
     584             ENDDO
     585
     586           ENDIF ! aeronlay_choice
     587
     588          ENDDO ! loop on n aerosol layers
     589
     590      end if ! if N-layer aerosols
     591 
    487592!==================================================================
    488593!    Jovian auroral aerosols (unknown composition) NON-GENERIC: vertical and meridional profile tuned to observations
     
    506611         
    507612 !       3. Meridional distribution, and re-normalize to observed total column
    508          tau_col(:)=0.D0
     613         dp_layer(:)=0.D0
    509614         DO ig=1,ngrid
    510615          !!Jupiter
     
    528633
    529634          DO l=1,nlayer 
    530                tau_col(ig) = tau_col(ig) + aerosol(ig,l,iaer)/obs_tau_col_aurora
     635               dp_layer(ig) = dp_layer(ig) + aerosol(ig,l,iaer)/obs_tau_col_aurora
    531636          ENDDO
    532637         ENDDO
     
    534639         DO ig=1,ngrid
    535640           DO l=1,nlayer-1
    536                 aerosol(ig,l,iaer)=aerosol(ig,l,iaer)/tau_col(ig)
     641                aerosol(ig,l,iaer)=aerosol(ig,l,iaer)/dp_layer(ig)
    537642           ENDDO
    538643         ENDDO
Note: See TracChangeset for help on using the changeset viewer.