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..

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
9 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
  • trunk/LMDZ.GENERIC/libf/phystd/aerosol_mod.F90

    r1677 r2297  
    1818 ! NH3 cloud
    1919      integer :: iaero_nh3 = 0
    20  ! Auroral aerosols
     20! N-layer aerosol model (replaces the 2-layer and hard-coded clouds)
     21      integer,dimension(:),allocatable,save :: iaero_nlay
     22! Auroral aerosols
    2123      integer :: iaero_aurora = 0
    22 !$OMP THREADPRIVATE(iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4,noaero,iaero_back2lay,iaero_nh3,iaero_aurora)
     24!$OMP THREADPRIVATE(iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4,noaero,iaero_back2lay,iaero_nh3,iaero_nlay,iaero_aurora)
    2325     
    2426!==================================================================
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r2283 r2297  
    2828      use gases_h, only: ngasmx
    2929      use radii_mod, only : su_aer_radii,co2_reffrad,h2o_reffrad,dust_reffrad,h2so4_reffrad,back2lay_reffrad
    30       use aerosol_mod, only : iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4, iaero_back2lay, iaero_nh3, iaero_aurora
     30      use aerosol_mod, only : iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4, iaero_back2lay, iaero_aurora
    3131      use tracer_h, only: igcm_h2o_vap, igcm_h2o_ice, igcm_co2_ice
    3232      use comcstfi_mod, only: pi, mugaz, cpp
     
    8282     
    8383      ! OUTPUT
    84       REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind) ! Aerosol tau.
     84      REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind) ! Aerosol tau at reference wavelenght.
    8585      REAL,INTENT(OUT) :: dtlw(ngrid,nlayer)             ! Heating rate (K/s) due to LW radiation.
    8686      REAL,INTENT(OUT) :: dtsw(ngrid,nlayer)             ! Heating rate (K/s) due to SW radiation.
     
    164164
    165165      ! Local aerosol optical properties for each column on RADIATIVE grid.
    166       real*8,save,allocatable ::  QXVAER(:,:,:)
     166      real*8,save,allocatable ::  QXVAER(:,:,:) ! Extinction coeff (QVISsQREF*QREFvis)
    167167      real*8,save,allocatable ::  QSVAER(:,:,:)
    168168      real*8,save,allocatable ::  GVAER(:,:,:)
    169       real*8,save,allocatable ::  QXIAER(:,:,:)
     169      real*8,save,allocatable ::  QXIAER(:,:,:) ! Extinction coeff (QIRsQREF*QREFir)
    170170      real*8,save,allocatable ::  QSIAER(:,:,:)
    171171      real*8,save,allocatable ::  GIAER(:,:,:)
     
    351351            call back2lay_reffrad(ngrid,reffrad(1,1,iaero_back2lay),nlayer,pplev)
    352352         endif
    353 !         if(iaer.eq.iaero_nh3)then
    354 !           call nh3_reffrad(ngrid,nlayer,reffrad(1,1,iaero_nh3))
    355 !         endif
     353
     354         !  For n-layer aerosol size set once for all at firstcall in su_aer_radii
     355
    356356!         if(iaer.eq.iaero_aurora)then
    357357!           call aurora_reffrad(ngrid,nlayer,reffrad(1,1,iaero_aurora))
     
    511511               pweight=(pplay(ig,L_NLAYRAD-k)-pplev(ig,L_NLAYRAD-k+1))/   &
    512512                       (pplev(ig,L_NLAYRAD-k)-pplev(ig,L_NLAYRAD-k+1))
     513               ! As 'aerosol' is at reference (visible) wavelenght we scale it as
     514               ! it will be multplied by qxi/v in optci/v
    513515               temp=aerosol(ig,L_NLAYRAD-k,iaer)/QREFvis3d(ig,L_NLAYRAD-k,iaer)
    514516               tauaero(2*k+2,iaer)=max(temp*pweight,0.d0)
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r2283 r2297  
    4343      logical,save :: aeroco2,aeroh2o,aeroh2so4,aeroback2lay
    4444!$OMP THREADPRIVATE(aeroco2,aeroh2o,aeroh2so4,aeroback2lay)
    45       logical,save :: aeronh3, aeroaurora
    46 !$OMP THREADPRIVATE(aeronh3,aeroaurora)
     45      logical,save :: aeronh3, aeronlay, aeroaurora
     46!$OMP THREADPRIVATE(aeronh3,aeronlay,aeroaurora)
    4747      logical,save :: aerofixco2,aerofixh2o
    4848!$OMP THREADPRIVATE(aerofixco2,aerofixh2o)
     
    6262!$OMP THREADPRIVATE(photochem)
    6363
    64       integer,save :: versH2H2cia
    6564      integer,save :: iddist
    6665      integer,save :: iaervar
    6766      integer,save :: iradia
    6867      integer,save :: startype
    69 !$OMP THREADPRIVATE(versH2H2cia,iddist,iaervar,iradia,startype)
     68      integer,save :: versH2H2cia
     69      integer,save :: nlayaero
     70!$OMP THREADPRIVATE(iddist,iaervar,iradia,startype,versH2H2cia,nlayaero)
     71      integer,dimension(:),allocatable,save :: aeronlay_choice
     72!$OMP THREADPRIVATE(aeronlay_choice)
     73
     74      character(64),save :: optprop_back2lay_vis
     75      character(64),save :: optprop_back2lay_ir
     76      character(64),dimension(:),allocatable,save :: optprop_aeronlay_vis
     77      character(64),dimension(:),allocatable,save :: optprop_aeronlay_ir
     78!$OMP THREADPRIVATE(optprop_back2lay_vis,optprop_back2lay_ir,optprop_aeronlay_vis,optprop_aeronlay_ir)
    7079
    7180      real,save :: tplanckmin
     
    8493      real,save :: obs_tau_col_strato
    8594!$OMP THREADPRIVATE(Tstrat,tplanet,obs_tau_col_tropo,obs_tau_col_strato)
    86       character(64),save :: optprop_back2lay_vis
    87       character(64),save :: optprop_back2lay_ir
    8895      real,save :: pres_bottom_tropo
    8996      real,save :: pres_top_tropo
     
    101108      real,save :: tau_nh3_cloud
    102109!$OMP THREADPRIVATE(size_nh3_cloud, pres_nh3_cloud, tau_nh3_cloud)
     110      real,dimension(:),allocatable,save :: aeronlay_tauref
     111      real,dimension(:),allocatable,save :: aeronlay_lamref
     112      real,dimension(:),allocatable,save :: aeronlay_ptop
     113      real,dimension(:),allocatable,save :: aeronlay_pbot
     114      real,dimension(:),allocatable,save :: aeronlay_sclhght
     115      real,dimension(:),allocatable,save :: aeronlay_size
     116!$OMP THREADPRIVATE(aeronlay_tauref,aeronlay_lamref,aeronlay_ptop,aeronlay_pbot,aeronlay_sclhght,aeronlay_size)
    103117      real,save :: co2supsat
    104118      real,save :: pceil
  • trunk/LMDZ.GENERIC/libf/phystd/iniaerosol.F

    r1677 r2297  
    55      use aerosol_mod
    66      use callkeys_mod, only: aeroco2,aeroh2o,dusttau,aeroh2so4,
    7      &          aeroback2lay,aeronh3, aeroaurora
     7     &          aeroback2lay,aeronh3, nlayaero, aeronlay, aeroaurora
    88
    99      IMPLICIT NONE
     
    1919c=======================================================================
    2020
    21       integer ia
     21      integer i, ia
     22
     23      ! Special case, dyn. allocation for n-layer depending on callphys.def
     24      IF(.NOT.ALLOCATED(iaero_nlay)) ALLOCATE(iaero_nlay(nlayaero))
     25      iaero_nlay(:) = 0
    2226
    2327      ia=0
     
    5862      write(*,*) '--- NH3 Cloud = ', iaero_nh3
    5963
     64      if (aeronlay) then
     65         do i=1,nlayaero
     66           ia=ia+1
     67           iaero_nlay(i)=ia
     68         enddo
     69      endif
     70      write(*,*) '--- N-layer aerosol = ', iaero_nlay
     71
    6072      if (aeroaurora) then
    6173         ia=ia+1
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r2283 r2297  
    554554     call getin_p("aeroh2so4",aeroh2so4)
    555555     write(*,*)" aeroh2so4 = ",aeroh2so4
    556          
     556 
     557     write(*,*)"Radiatively active auroral aerosols?"
     558     aeroaurora=.false.     ! default value
     559     call getin_p("aeroaurora",aeroaurora)
     560     write(*,*)" aeroaurora = ",aeroaurora
     561
    557562!=================================
     563! TWOLAY scheme and NH3 cloudare left for retrocompatibility only,
     564! You should now use N-LAYER scheme (see below).
    558565
    559566     write(*,*)"Radiatively active two-layer aerosols?"
     
    562569     write(*,*)" aeroback2lay = ",aeroback2lay
    563570
     571     if (aeroback2lay) then
     572       print*,'Warning : The TWOLAY AEROSOL scheme is deprecated and buggy...'
     573       print*,'You should use the generic n-layer scheme (see aeronlay).'
     574     endif
     575
    564576     write(*,*)"Radiatively active ammonia cloud?"
    565577     aeronh3=.false.     ! default value
     
    567579     write(*,*)" aeronh3 = ",aeronh3
    568580
    569      write(*,*)"Radiatively active auroral aerosols?"
    570      aeroaurora=.false.     ! default value
    571      call getin_p("aeroaurora",aeroaurora)
    572      write(*,*)" aeroaurora = ",aeroaurora
     581     if (aeronh3) then
     582       print*,'Warning : You are using specific NH3 cloud scheme ...'
     583       print*,'You should use the generic n-layer scheme (see aeronlay).'
     584     endif
    573585
    574586     write(*,*)"TWOLAY AEROSOL: total optical depth ", &
     
    613625       print*,'Error : TWOLAY AEROSOL, Please ensure that in callphys.def'
    614626       print*,'you have pres_top_tropo > pres_bottom_strato !'
    615        stop
     627       call abort
    616628     endif
    617629
     
    647659     call getin_p("size_nh3_cloud",size_nh3_cloud)
    648660     write(*,*)" size_nh3_cloud = ",size_nh3_cloud
     661
     662!=================================
     663! Generic N-LAYER aerosol scheme
     664
     665     write(*,*)"Radiatively active generic n-layer aerosols?"
     666     aeronlay=.false.     ! default value
     667     call getin_p("aeronlay",aeronlay)
     668     write(*,*)" aeronlay = ",aeronlay
     669
     670     write(*,*)"Number of generic aerosols layers?"
     671     nlayaero=1     ! default value
     672     call getin_p("nlayaero",nlayaero)
     673     ! Avoid to allocate arrays of size 0
     674     if (aeronlay .and. nlayaero.lt.1) then
     675       print*, " You are trying to set no generic aerosols..."
     676       print*, " Set aeronlay=.false. instead ! I abort."
     677       call abort
     678     endif
     679     if (.not. aeronlay) nlayaero=1
     680     write(*,*)" nlayaero = ",nlayaero
     681
     682     ! This is necessary, we just set the number of aerosol layers
     683     IF(.NOT.ALLOCATED(aeronlay_tauref))      ALLOCATE(aeronlay_tauref(nlayaero))     
     684     IF(.NOT.ALLOCATED(aeronlay_lamref))      ALLOCATE(aeronlay_lamref(nlayaero))     
     685     IF(.NOT.ALLOCATED(aeronlay_choice))      ALLOCATE(aeronlay_choice(nlayaero))     
     686     IF(.NOT.ALLOCATED(aeronlay_pbot))        ALLOCATE(aeronlay_pbot(nlayaero))     
     687     IF(.NOT.ALLOCATED(aeronlay_ptop))        ALLOCATE(aeronlay_ptop(nlayaero))     
     688     IF(.NOT.ALLOCATED(aeronlay_sclhght))     ALLOCATE(aeronlay_sclhght(nlayaero))     
     689     IF(.NOT.ALLOCATED(aeronlay_size))        ALLOCATE(aeronlay_size(nlayaero))     
     690     IF(.NOT.ALLOCATED(optprop_aeronlay_ir))  ALLOCATE(optprop_aeronlay_ir(nlayaero))     
     691     IF(.NOT.ALLOCATED(optprop_aeronlay_vis)) ALLOCATE(optprop_aeronlay_vis(nlayaero))     
     692
     693     write(*,*)"Generic n-layer aerosols: Optical depth at reference wavelenght"
     694     aeronlay_tauref=1.0E-1
     695     call getin_p("aeronlay_tauref",aeronlay_tauref)
     696     write(*,*)" aeronlay_tauref = ",aeronlay_tauref
     697
     698     write(*,*)"Generic n-layer aerosols: Reference wavelenght for optical depths (m)"
     699     aeronlay_lamref=0.6E-6
     700     call getin_p("aeronlay_lamref",aeronlay_lamref)
     701     write(*,*)" aeronlay_lamref = ",aeronlay_lamref
     702
     703     write(*,*)"Generic n-layer aerosols: Vertical profile choice : &
     704                     (1) Tau btwn ptop and pbot follows atm. scale height &
     705                 or  (2) Tau above pbot follows its own scale height"
     706     aeronlay_choice=1
     707     call getin_p("aeronlay_choice",aeronlay_choice)
     708     write(*,*)" aeronlay_choice = ",aeronlay_choice
     709
     710     write(*,*)"Generic n-layer aerosols: bottom pressures (Pa)"
     711     aeronlay_pbot=2000.0
     712     call getin_p("aeronlay_pbot",aeronlay_pbot)
     713     write(*,*)" aeronlay_pbot = ",aeronlay_pbot
     714
     715     write(*,*)"Generic n-layer aerosols: (if choice=1) Top pressures (Pa) "
     716     aeronlay_ptop=300000.0
     717     call getin_p("aeronlay_ptop",aeronlay_ptop)
     718     write(*,*)" aeronlay_ptop = ",aeronlay_ptop
     719
     720     write(*,*)"Generic n-layer aerosols: (if choice=2) Scale height / atm. scale height"
     721     aeronlay_ptop=0.2
     722     call getin_p("aeronlay_sclhght",aeronlay_sclhght)
     723     write(*,*)" aeronlay_sclhght = ",aeronlay_sclhght
     724
     725     write(*,*)"Generic n-layer aerosols: particles sizes (m)"
     726     aeronlay_size=1.e-6
     727     call getin_p("aeronlay_size",aeronlay_size)
     728     write(*,*)" aeronlay_size = ",aeronlay_size
     729
     730     write(*,*)"Generic n-layer aerosols: VIS optical properties file"
     731     optprop_aeronlay_vis = 'optprop_saturn_vis_n20.dat'
     732     call getin_p("optprop_aeronlay_vis",optprop_aeronlay_vis)
     733     write(*,*)" optprop_aeronlay_vis = ",optprop_aeronlay_vis
     734
     735     write(*,*)"Generic n-layer aerosols: IR optical properties file"
     736     optprop_aeronlay_ir = 'optprop_saturn_ir_n20.dat'
     737     call getin_p("optprop_aeronlay_ir",optprop_aeronlay_ir)
     738     write(*,*)" optprop_aeronlay_ir = ",optprop_aeronlay_ir
     739     
    649740
    650741!=================================
  • trunk/LMDZ.GENERIC/libf/phystd/radcommon_h.F90

    r2283 r2297  
    5757!
    5858! For the "naerkind" kind of aerosol radiative properties :
    59 ! QIRsQREF :  Qext / Qext("longrefvis")
     59! QIRsQREF :  Qext / Qext("longrefir")
    6060! omegaIR  :  mean single scattering albedo
    6161! gIR      :  mean assymetry factor
     62!
     63!
     64! Note - QIRsQREF in the martian model was scaled to longrefvis,
     65! here it is scaled to longrefir, which is actually a dummy parameter,
     66! as we do not output scaled aerosol opacity ...
     67!
    6268
    6369      REAL*8 BWNI(L_NSPECTI+1), WNOI(L_NSPECTI), DWNI(L_NSPECTI), WAVEI(L_NSPECTI) !BWNI read by master in setspi
  • trunk/LMDZ.GENERIC/libf/phystd/radii_mod.F90

    r2005 r2297  
    88!     water cloud optical properties
    99
    10       use callkeys_mod, only: radfixed,Nmix_co2,                    &
    11                 pres_bottom_tropo,pres_top_tropo,size_tropo,        &
    12                 pres_bottom_strato,size_strato
     10      use callkeys_mod, only: radfixed,Nmix_co2
    1311     
    1412      real, save ::  rad_h2o
     
    3937      use radinc_h, only: naerkind
    4038      use aerosol_mod, only: iaero_back2lay, iaero_co2, iaero_dust, &
    41                              iaero_h2o, iaero_h2so4,iaero_nh3,iaero_aurora
    42       use callkeys_mod, only: size_nh3_cloud
     39                             iaero_h2o, iaero_h2so4, iaero_nh3, iaero_nlay, iaero_aurora
     40      use callkeys_mod, only: size_nh3_cloud, nlayaero, aeronlay_size
    4341
    4442      Implicit none
     
    5250      logical, save :: firstcall=.true.
    5351!$OMP THREADPRIVATE(firstcall)
    54       integer :: iaer   
     52      integer :: iaer, ia   
    5553     
    5654      print*,'enter su_aer_radii'
     
    6058!     a fixed aerosol layer, and be able to define reffrad in a
    6159!     .def file. To be improved!
     60!                |-> Done in th n-layer aerosol case (JVO 20)
    6261
    6362            if(iaer.eq.iaero_co2)then ! CO2 ice
     
    9190               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    9291            endif
     92
     93            do ia=1,nlayaero
     94              if(iaer.eq.iaero_nlay(ia))then ! N-layer aerosols
     95                 reffrad(1:ngrid,1:nlayer,iaer) = aeronlay_size(ia)
     96                 nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
     97              endif
     98            enddo
    9399
    94100            if(iaer.eq.iaero_aurora)then ! Auroral aerosols
     
    345351!
    346352!==================================================================
     353      use callkeys_mod, only: pres_bottom_tropo,pres_top_tropo,size_tropo,  &
     354                              pres_bottom_strato,size_strato
    347355 
    348       use aerosol_mod   !! Particle sizes and boundaries of aerosol layers defined there
    349      Implicit none
     356      Implicit none
    350357
    351358      integer,intent(in) :: ngrid
  • trunk/LMDZ.GENERIC/libf/phystd/suaer_corrk.F90

    r2062 r2297  
    1111      use radcommon_h, only: qrefvis,qrefir,omegarefir !,omegarefvis
    1212      use aerosol_mod
    13       use callkeys_mod, only: tplanet, optprop_back2lay_vis, optprop_back2lay_ir
     13      use callkeys_mod, only: tplanet, optprop_back2lay_vis, optprop_back2lay_ir, &
     14                              optprop_aeronlay_vis, optprop_aeronlay_ir,          &
     15                              aeronlay_lamref, nlayaero
    1416
    1517      implicit none
     
    8082      REAL epref                       ! reference extinction ep
    8183
    82 !      REAL epav(L_NSPECTI)            ! Average ep (= <Qext>/Qext(lamref) if epref=1)
    83 !      REAL omegav(L_NSPECTI)          ! Average single scattering albedo
    84 !      REAL gav(L_NSPECTI)             ! Average assymetry parameter
    85 
    86       REAL epavVI(L_NSPECTV)            ! Average ep (= <Qext>/Qext(lamref) if epref=1)
     84      REAL epavVI(L_NSPECTV)            ! Average ep (= <Qext>/Qext(lamrefvis) if epref=1)
    8785      REAL omegavVI(L_NSPECTV)          ! Average single scattering albedo
    8886      REAL gavVI(L_NSPECTV)             ! Average assymetry parameter
    8987
    90       REAL epavIR(L_NSPECTI)            ! Average ep (= <Qext>/Qext(lamref) if epref=1)
     88      REAL epavIR(L_NSPECTI)            ! Average ep (= <Qext>/Qext(lamrefir) if epref=1)
    9189      REAL omegavIR(L_NSPECTI)          ! Average single scattering albedo
    9290      REAL gavIR(L_NSPECTI)             ! Average assymetry parameter
    9391     
    9492      logical forgetit                  ! use francois' data?
    95       integer iwvl
     93      integer iwvl, ia
    9694
    9795!     Local saved variables:
    9896
    99       CHARACTER(LEN=30), DIMENSION(naerkind,2), SAVE :: file_id
     97      CHARACTER(LEN=50), DIMENSION(naerkind,2), SAVE :: file_id
    10098!$OMP THREADPRIVATE(file_id)
    10199!---- Please indicate the names of the optical property files below
    102100!     Please also choose the reference wavelengths of each aerosol     
     101
     102!--------- README TO UNDERSTAND WHAT FOLLOWS (JVO 20) -------
     103!     The lamref variables comes from the Martian model
     104!     where the visible one is the one used for computing
     105!     and the IR one is used to output scaled opacity to
     106!     match instrumental data ... This is done (at least
     107!     for now) in the generic, so lamrefir is dummy*!
     108
     109!     The important one is the VISIBLE one as it will be used
     110!     to rescale the values in callcork.F90 assuming 'aerosol' is
     111!     at this visible reference wavelenght.
     112
     113!     *Actually if you change lamrefir here there is a
     114!     slight sensitvity in the outputs because of some
     115!     machine precision differences that amplifys and lead
     116!     up to 10-6 differences in the radiative balance...
     117!     This could be good to clean the code but would require
     118!     a lot of modifs and to take care !
     119
     120!--------------------------------------------------------------
    103121
    104122      if (noaero) then
     
    125143           file_id(iaer,2) = 'optprop_co2ice_ir_n50.dat'
    126144        endif
    127         lamrefir(iaer)=12.1E-6   ! 825cm-1 TES/MGS ???
     145        lamrefir(iaer)=12.1E-6   ! Dummy in generic phys. (JVO 20)
    128146       endif ! CO2 aerosols 
    129147! NOTE: these lamref's are currently for dust, not CO2 ice.
     
    139157!     infrared
    140158         file_id(iaer,2) = 'optprop_iceir_n50.dat'
    141          lamrefir(iaer)=12.1E-6   ! 825cm-1 TES/MGS
     159         lamrefir(iaer)=12.1E-6   ! Dummy in generic phys. (JVO 20)
    142160       endif
    143161
     
    151169!     infrared
    152170         file_id(iaer,2) = 'optprop_dustir_n50.dat'
    153          !lamrefir(iaer)=12.1E-6   ! 825cm-1 TES/MGS
    154          lamrefir(iaer)=9.3E-6
     171         lamrefir(iaer)=9.3E-6     ! Dummy in generic phys. (JVO 20)
    155172       endif
    156173
     
    160177!     visible
    161178         file_id(iaer,1) = 'optprop_h2so4vis_n20.dat'
    162          !lamrefir(iaer)=  doesn't exist?
    163179         lamrefvis(iaer)=1.5E-6   ! no idea, must find
    164180!     infrared
    165181         file_id(iaer,2) = 'optprop_h2so4ir_n20.dat'
    166          !lamrefir(iaer)=12.1E-6   ! 825cm-1 TES/MGS
    167          lamrefir(iaer)=9.3E-6 ! no idea, must find
     182         lamrefir(iaer)=9.3E-6 ! ! Dummy in generic phys. (JVO 20)
    168183! added by LK
    169184       endif
     
    174189!     visible
    175190         file_id(iaer,1) = TRIM(optprop_back2lay_vis)
    176          lamrefvis(iaer)=0.8E-6  !
     191         lamrefvis(iaer)=0.8E-6  ! This is the important one.
    177192!     infrared
    178193         file_id(iaer,2) = TRIM(optprop_back2lay_ir)
    179          lamrefir(iaer)=6.E-6  !
     194         lamrefir(iaer)=6.E-6    ! This is dummy.
    180195! added by SG
    181196       endif
     
    189204!     infrared
    190205         file_id(iaer,2) = 'optprop_nh3ice_ir.dat'
    191          lamrefir(iaer)=6.E-6  !
     206         lamrefir(iaer)=6.E-6  ! dummy
    192207! added by SG
    193208       endif
    194209
     210       do ia=1,nlayaero
     211         if (iaer.eq.iaero_nlay(ia)) then
     212           print*, 'naerkind= nlay', iaer
     213           
     214!       visible
     215           file_id(iaer,1) = TRIM(optprop_aeronlay_vis(ia))
     216           lamrefvis(iaer)=aeronlay_lamref(ia)
     217!       infrared
     218           file_id(iaer,2) = TRIM(optprop_aeronlay_ir(ia))
     219           lamrefir(iaer)=6.E-6 ! Dummy value
     220         endif
     221       enddo
     222! added by JVO
     223     
    195224       if (iaer.eq.iaero_aurora) then
    196225         print*, 'naerkind= aurora', iaer
     
    201230!     infrared
    202231         file_id(iaer,2) = 'optprop_aurora_ir.dat'
    203          lamrefir(iaer)=6.E-6  !
     232         lamrefir(iaer)=6.E-6  ! dummy
    204233! added by SG
    205234       endif
Note: See TracChangeset for help on using the changeset viewer.