Ignore:
Timestamp:
Aug 30, 2013, 4:00:31 PM (11 years ago)
Author:
sglmd
Message:

Added a flexible, 2-layer aerosol scenario (initially for Saturn, but can be simply tuned). Called aeroback2lay.

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

Legend:

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

    r858 r1026  
    6767
    6868      LOGICAL,SAVE :: firstcall=.true.
    69 
    7069      REAL CBRT
    7170      EXTERNAL CBRT
     
    119118        if (iaero_h2so4.ne.0) then
    120119          print*,'iaero_h2so4= ',iaero_h2so4
     120        endif
     121        if (iaero_back2lay.ne.0) then
     122          print*,'iaero_back2lay= ',iaero_back2lay
    121123        endif
    122124
     
    356358 
    357359           
     360!     ---------------------------------------------------------
     361!==================================================================
     362!    Two-layer aerosols (unknown composition)
     363!    S. Guerlet (2013)
     364!==================================================================
     365
     366      if (iaero_back2lay .ne.0) then
     367           iaer=iaero_back2lay
     368!       1. Initialization
     369            aerosol(1:ngrid,1:nlayermx,iaer)=0.0
     370!       2. Opacity calculation
     371          DO ig=1,ngrid
     372           DO l=1,nlayer-1
     373             aerosol(ig,l,iaer) = ( pplev(ig,l) - pplev(ig,l+1) )
     374             !! 1. below tropospheric layer: no aerosols
     375             IF (pplev(ig,l) .gt. pres_bottom_tropo) THEN
     376               aerosol(ig,l,iaer) = 0.*aerosol(ig,l,iaer)
     377             !! 2. tropo layer
     378             ELSEIF (pplev(ig,l) .le. pres_bottom_tropo .and. pplev(ig,l) .ge. pres_top_tropo) THEN
     379               aerosol(ig,l,iaer) = obs_tau_col_tropo*aerosol(ig,l,iaer)
     380             !! 3. linear transition
     381             ELSEIF (pplev(ig,l) .lt. pres_top_tropo .and. pplev(ig,l) .gt. pres_bottom_strato) THEN
     382               expfactor=log(obs_tau_col_strato/obs_tau_col_tropo)/log(pres_bottom_strato/pres_top_tropo)
     383               aerosol(ig,l,iaer)= obs_tau_col_tropo*((pplev(ig,l)/pres_top_tropo)**expfactor)*aerosol(ig,l,iaer)
     384             !! 4. strato layer
     385             ELSEIF (pplev(ig,l) .le. pres_bottom_strato .and. pplev(ig,l) .gt. pres_top_strato) THEN
     386               aerosol(ig,l,iaer)= obs_tau_col_strato*aerosol(ig,l,iaer)
     387             !! 5. above strato layer: no aerosols
     388             ELSEIF (pplev(ig,l) .lt. pres_top_strato) THEN
     389               aerosol(ig,l,iaer) = 0.*aerosol(ig,l,iaer)
     390             ENDIF
     391           ENDDO
     392          ENDDO
     393
     394 !       3. Re-normalize to observed total column
     395         tau_col(:)=0.0
     396         DO l=1,nlayer
     397          DO ig=1,ngrid
     398               tau_col(ig) = tau_col(ig) &
     399                     + aerosol(ig,l,iaer)/(obs_tau_col_tropo+obs_tau_col_strato)
     400            ENDDO
     401         ENDDO
     402
     403         DO ig=1,ngrid
     404           DO l=1,nlayer-1
     405                aerosol(ig,l,iaer)=aerosol(ig,l,iaer)/tau_col(ig)
     406           ENDDO
     407         ENDDO
     408
     409
     410      end if ! if Two-layer aerosols 
     411
    358412
    359413! --------------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/aerosol_mod.F90

    r747 r1026  
    1313      integer :: iaero_h2so4 = 0
    1414      logical :: noaero = .false.
     15
     16! two-layer simple aerosol model
     17      integer :: iaero_back2lay = 0
     18      REAL :: obs_tau_col_tropo  !! observed total optical depth in the tropospheric layer (visible)
     19      REAL :: obs_tau_col_strato !! observed total optical depth in the stratospheric layer (visible)
     20      REAL :: pres_bottom_tropo  !! In Pa !   
     21      REAL :: pres_top_tropo     !! In Pa
     22      REAL :: pres_bottom_strato  !! In Pa
     23      REAL :: pres_top_strato     !! In Pa
     24      REAL :: size_tropo  !! particle size in the tropospheric layer
     25      REAL :: size_strato !! particle size in the stratospheric layer
    1526     
    1627!==================================================================
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r1016 r1026  
    1414      use ioipsl_getincom
    1515      use gases_h
    16       use radii_mod, only : su_aer_radii,co2_reffrad,h2o_reffrad,dust_reffrad,h2so4_reffrad
    17       use aerosol_mod, only : iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4
     16      use radii_mod, only : su_aer_radii,co2_reffrad,h2o_reffrad,dust_reffrad,h2so4_reffrad,back2lay_reffrad
     17      use aerosol_mod, only : iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4, iaero_back2lay
    1818      USE tracer_h
    1919
     
    286286            print*,'H2SO4 particle size =',reffrad(1,1,iaer)/1.e-6,' um'
    287287         endif
    288       end do !iaer=1,naerkind
     288          if(iaer.eq.iaero_back2lay)then
     289            call back2lay_reffrad(ngrid,reffrad(1,1,iaero_back2lay),nlayer,pplev)
     290         endif
     291     end do !iaer=1,naerkind
    289292
    290293
     
    302305           reffrad,QREFvis3d,QREFir3d,                             &
    303306           tau_col,cloudfrac,totcloudfrac,clearsky)                ! get aerosol optical depths
    304 
     307         
    305308!-----------------------------------------------------------------------
    306309!     Starting Big Loop over every GCM column
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys.h

    r952 r1026  
    2222     &   , tracer, mass_redistrib, varactive, varfixed, satval          &
    2323     &   , sedimentation,water,watercond,waterrain                      &
    24      &   , aeroco2,aeroh2o,aeroh2so4                                    &
     24     &   , aeroco2,aeroh2o,aeroh2so4,aeroback2lay                         &
    2525     &   , aerofixco2,aerofixh2o                                        &
    2626     &   , hydrology, sourceevol, icetstep, albedosnow                  &
     
    5858      logical sedimentation
    5959      logical water,watercond,waterrain
    60       logical aeroco2,aeroh2o,aeroh2so4 
     60      logical aeroco2,aeroh2o,aeroh2so4,aeroback2lay
    6161      logical aerofixco2,aerofixh2o
    6262      logical hydrology
  • trunk/LMDZ.GENERIC/libf/phystd/iniaerosol.F

    r747 r1026  
    1212c   (CO2 aerosols, dust, water, chemical species, ice...)   
    1313c
    14 c   author: Laura Kerber
     14c   author: Laura Kerber, S. Guerlet
    1515c   ------
    1616c       
     
    4646      write(*,*) '--- H2SO4 aerosol = ', iaero_h2so4
    4747     
     48      if (aeroback2lay) then
     49         ia=ia+1
     50         iaero_back2lay=ia
     51         !! define aerosols parameters (should be in a .def?)
     52         !! Saturn: Roman et al. Icarus 2013 2-layer scenario (ISS observations)
     53         obs_tau_col_tropo=8.D0       !! observed total optical depth in the tropospheric layer (visible)
     54         obs_tau_col_strato=0.08D0    !! observed total optical depth in the stratospheric layer (visible)
     55         pres_bottom_tropo= 66000.0   !! In Pa !   
     56         pres_top_tropo= 18000.0      !! In Pa
     57         pres_bottom_strato= 10000.0  !! In Pa
     58         pres_top_strato= 100.0       !! In Pa
     59         size_tropo=2.e-6     !! particle size in the tropospheric layer, in meters
     60         size_strato=1.e-7    !! particle size in the stratospheric layer
     61      endif
     62      write(*,*) '--- Two-layer aerosol = ', iaero_back2lay
     63
     64     
    4865      write(*,*) '=== Number of aerosols= ', ia
    4966     
  • trunk/LMDZ.GENERIC/libf/phystd/inifis.F

    r961 r1026  
    431431         call getin("aeroh2so4",aeroh2so4)
    432432         write(*,*)" aeroh2so4 = ",aeroh2so4
     433         
     434         write(*,*)"Radiatively active two-layer aersols?"
     435         aeroback2lay=.false.     ! default value
     436         call getin("aeroback2lay",aeroback2lay)
     437         write(*,*)" aeroback2lay = ",aeroback2lay
     438
    433439
    434440         write(*,*)"Cloud pressure level (with kastprof only):"
  • trunk/LMDZ.GENERIC/libf/phystd/radii_mod.F90

    r863 r1026  
    7676               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
    7777            endif
    78 
    79             if(iaer.gt.4)then
    80                print*,'Error in callcorrk, naerkind is too high (>4).'
     78           
     79            if(iaer.eq.iaero_back2lay)then ! Two-layer aerosols
     80               reffrad(1:ngrid,1:nlayermx,iaer) = 2.e-6
     81               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
     82            endif
     83
     84
     85
     86            if(iaer.gt.5)then
     87               print*,'Error in callcorrk, naerkind is too high (>5).'
    8188               print*,'The code still needs generalisation to arbitrary'
    8289               print*,'aerosol kinds and number.'
     
    323330!==================================================================
    324331
     332!==================================================================
     333   subroutine back2lay_reffrad(ngrid,reffrad,nlayer,pplev)
     334!==================================================================
     335!     Purpose
     336!     -------
     337!     Compute the effective radii of particles in a 2-layer model
     338!
     339!     Authors
     340!     -------
     341!     Sandrine Guerlet (2013)
     342!
     343!==================================================================
     344 
     345      use aerosol_mod   !! Particle sizes and boundaries of aerosol layers defined there
     346     Implicit none
     347
     348#include "callkeys.h"
     349#include "dimensions.h"
     350#include "dimphys.h"
     351
     352      integer,intent(in) :: ngrid
     353
     354      real, intent(out) :: reffrad(ngrid,nlayermx)      ! particle radii
     355      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! inter-layer pressure (Pa)
     356      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
     357      REAL :: expfactor
     358      INTEGER l,ig
     359           
     360      reffrad(:,:)=1e-6  !!initialization, not important
     361          DO ig=1,ngrid
     362            DO l=1,nlayer-1
     363              IF (pplev(ig,l) .le. pres_bottom_tropo .and. pplev(ig,l) .ge. pres_top_tropo) THEN
     364                reffrad(ig,l) = size_tropo
     365              ELSEIF (pplev(ig,l) .lt. pres_top_tropo .and. pplev(ig,l) .gt. pres_bottom_strato) THEN
     366                expfactor=log(size_strato/size_tropo) / log(pres_bottom_strato/pres_top_tropo)
     367                reffrad(ig,l)= size_tropo*((pplev(ig,l)/pres_top_tropo)**expfactor)
     368              ELSEIF (pplev(ig,l) .le. pres_bottom_strato) then
     369                reffrad(ig,l) = size_strato
     370              ENDIF
     371            ENDDO
     372          ENDDO
     373
     374   end subroutine back2lay_reffrad
     375!==================================================================
     376
    325377
    326378
  • trunk/LMDZ.GENERIC/libf/phystd/suaer_corrk.F90

    r804 r1026  
    167167! added by LK
    168168       endif
     169
     170       if (iaer.eq.iaero_back2lay) then
     171         print*, 'naerkind= back2lay', iaer
     172
     173!     visible
     174         file_id(iaer,1) = 'optprop_saturn_vis_n20.dat'
     175         lamrefvis(iaer)=0.8E-6  !
     176!     infrared
     177         file_id(iaer,2) = 'optprop_saturn_ir_n20.dat'
     178         lamrefir(iaer)=6.E-6  !
     179! added by SG
     180       endif
     181       
    169182       
    170183      enddo
Note: See TracChangeset for help on using the changeset viewer.