Changeset 1764 for LMDZ5/trunk/libf


Ignore:
Timestamp:
Jun 10, 2013, 3:40:50 PM (11 years ago)
Author:
Laurent Fairhead
Message:

Inclusion d'une routine qui lit des champs d'aérosols stratosphériques
mensuels, prescrit des propriétés optiques et modifie le rayonnement en
conséquence. Pour le moment, seule l'interaction avec le rayonnement ondes
courtes est pris en compte. Les fichiers d'input doivent être au format des
fichiers de sortie. Contrôlé par la variable logique: flag_aerosol_strat
(false par défaut dans DefLists?/config.def)

  1. Boucher

A new routine has been added to the code that reads in monthly stratospheric
aerosols, prescribes optical properties and modifies radiation accordingly.
Presently, only the interaction with short wave radiation is taken into account.
Input files must be formatted as are the aerosol output fields. Control is by
the logical flag: flag_aerosol_strat (which is false by default and included
DefLists?/config.def)

  1. Boucher
Location:
LMDZ5/trunk/libf/phylmd
Files:
1 added
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/aero_mod.F90

    r1279 r1764  
    55
    66  ! Total number of aerosols
    7   INTEGER, PARAMETER :: naero_tot = 10
     7!  INTEGER, PARAMETER :: naero_tot = 10
     8!--STRAT AER
     9  INTEGER, PARAMETER :: naero_tot = 11
    810
    911  ! Identification number used in aeropt_2bands and aeropt_5wv
     
    1921  INTEGER, PARAMETER :: id_AIBCM    = 9
    2022  INTEGER, PARAMETER :: id_AIPOMM   = 10
     23!--STRAT AER
     24  INTEGER, PARAMETER :: id_strat   = 11
     25
    2126
    2227  ! Total number of aerosols actually used in LMDZ
     
    3136  ! 9 =  AIBCM
    3237  !10 =  AIPOMM
    33   INTEGER, PARAMETER :: naero_spc = 10
     38!--STRAT AER
     39  !11 = aerosols stratos
     40!  INTEGER, PARAMETER :: naero_spc = 10
     41  INTEGER, PARAMETER :: naero_spc = 11
    3442
    3543  ! Corresponding names for the aerosols
     
    4452       "CIDUSTM", &
    4553       "AIBCM  ", &
    46        "AIPOMM " /)
     54!       "AIPOMM " /)
     55       "AIPOMM ", &
     56       "STRAT  " /)
    4757
    4858
     
    6575  INTEGER, parameter :: nbands = 2
    6676
    67 
    6877END MODULE aero_mod
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r1753 r1764  
    1818                       iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    1919                       ok_ade, ok_aie, ok_cdnc, aerosol_couple, &
    20                        flag_aerosol, new_aod, &
     20                       flag_aerosol, flag_aerosol_strat, new_aod, &
    2121                       bl95_b0, bl95_b1,&
    2222                       read_climoz, &
     
    6060! ok_ade, ok_aie: apply or not aerosol direct and indirect effects
    6161! ok_cdnc, ok cloud droplet number concentration
     62! flag_aerosol_strat : flag pour les aerosols stratos
    6263! bl95_b*: parameters in the formula to link CDNC to aerosol mass conc
    6364!
     
    7273  LOGICAL              :: ok_ade, ok_aie, ok_cdnc, aerosol_couple
    7374  INTEGER              :: flag_aerosol
     75  LOGICAL              :: flag_aerosol_strat
    7476  LOGICAL              :: new_aod
    7577  REAL                 :: bl95_b0, bl95_b1
     
    8789  LOGICAL,SAVE        :: ok_ade_omp, ok_aie_omp, ok_cdnc_omp, aerosol_couple_omp
    8890  INTEGER, SAVE       :: flag_aerosol_omp
     91  INTEGER, SAVE       :: flag_aerosol_strat_omp
    8992  LOGICAL, SAVE       :: new_aod_omp
    9093  REAL,SAVE           :: bl95_b0_omp, bl95_b1_omp
     
    307310  flag_aerosol_omp = 0
    308311  CALL getin('flag_aerosol',flag_aerosol_omp)
     312!
     313!Config Key  = flag_aerosol_strat
     314!Config Desc = use stratospheric aerosols T/F
     315!Config Def  = false
     316!Config Help = Used in physiq.F
     317!
     318!
     319  flag_aerosol_strat_omp = .false.
     320  CALL getin('flag_aerosol_strat',flag_aerosol_strat_omp)
    309321
    310322! Temporary variable for testing purpose!!
     
    17171729    aerosol_couple = aerosol_couple_omp
    17181730    flag_aerosol=flag_aerosol_omp
     1731    flag_aerosol_strat=flag_aerosol_strat_omp
    17191732    new_aod=new_aod_omp
    17201733    aer_type = aer_type_omp
     
    19011914  write(lunout,*)' aerosol_couple = ', aerosol_couple
    19021915  write(lunout,*)' flag_aerosol = ', flag_aerosol
     1916  write(lunout,*)' flag_aerosol_strat = ', flag_aerosol_strat
    19031917  write(lunout,*)' new_aod = ', new_aod
    19041918  write(lunout,*)' aer_type = ',aer_type
  • LMDZ5/trunk/libf/phylmd/etat0_netcdf.F90

    r1727 r1764  
    101101  LOGICAL :: ok_LES, ok_ade, ok_aie, ok_cdnc, aerosol_couple, new_aod, callstats
    102102  INTEGER :: iflag_radia, flag_aerosol
     103  LOGICAL :: flag_aerosol_strat
    103104  REAL    :: bl95_b0, bl95_b1, fact_cldcon, facttemps, ratqsbas, ratqshaut
    104105  REAL    :: tau_ratqs
     
    137138                   iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs,            &
    138139                   ok_ade, ok_aie, ok_cdnc, aerosol_couple,             &
    139                    flag_aerosol, new_aod,                               &
     140                   flag_aerosol, flag_aerosol_strat, new_aod,           &
    140141                   bl95_b0, bl95_b1,                                    &
    141142                   read_climoz,                                         &
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r1761 r1764  
    410410  type(ctrl_out),save :: o_solswai      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswai')
    411411
    412   type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
     412!  type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
     413  type(ctrl_out),save,dimension(11) :: o_tausumaero  = &
     414    (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
    413415       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), &
    414416       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), &
     
    419421       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), &
    420422       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), &
    421        ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM') /)
     423       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM'), &
     424       ctrl_out((/ 2, 2, 10, 10, 10, 10 /),'OD550_STRAT') /)
    422425
    423426  type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550aer')
     
    579582  type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'e_th')
    580583  type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'w_th')
     584  type(ctrl_out),save :: o_lambda_th    = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'lambda_th')
    581585  type(ctrl_out),save :: o_ftime_th     = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_th')
    582586  type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'q_th')
     
    663667       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
    664668       phys_out_filestations, &
    665        new_aod, aerosol_couple)   
     669       new_aod, aerosol_couple, flag_aerosol_strat)   
    666670
    667671    USE iophy
     
    693697    integer                               :: nbteta, nlevSTD, radpas
    694698    logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
    695     logical                               :: ok_LES,ok_ade,ok_aie
     699    logical                               :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat
    696700    logical                               :: new_aod, aerosol_couple
    697701    integer, intent(in)::  read_climoz ! read ozone climatology
     
    11651169                CALL histdef2d(iff,clef_stations(iff), &
    11661170                     o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
    1167 
     1171!--STRAT AER
     1172             ENDIF
     1173             IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN
    11681174                DO naero = 1, naero_spc
    11691175                   CALL histdef2d(iff,clef_stations(iff), &
     
    16501656             CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
    16511657             CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
     1658             CALL histdef3d(iff,clef_stations(iff), &
     1659                  o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
    16521660             CALL histdef2d(iff,clef_stations(iff), &
    16531661                  o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
  • LMDZ5/trunk/libf/phylmd/phys_output_write.h

    r1761 r1764  
    13051305          ENDIF
    13061306         
     1307c--STRAT AER
     1308          endif
     1309          IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN
    13071310          DO naero = 1, naero_spc
    13081311            IF (o_tausumaero(naero)%flag(iff)<=lev_files(iff)) THEN
  • LMDZ5/trunk/libf/phylmd/physiq.F

    r1761 r1764  
    11201120      LOGICAL, SAVE :: new_aod
    11211121c$OMP THREADPRIVATE(new_aod)
    1122    
     1122c
     1123c--STRAT AEROSOL
     1124      LOGICAL, SAVE :: flag_aerosol_strat
     1125c$OMP THREADPRIVATE(flag_aerosol_strat)
     1126cc-fin STRAT AEROSOL
    11231127c
    11241128c Declaration des constantes et des fonctions thermodynamiques
     
    12701274     .     iflag_cldcon,iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs,
    12711275     .     ok_ade, ok_aie, ok_cdnc, aerosol_couple,
    1272      .     flag_aerosol, new_aod,
     1276     .     flag_aerosol, flag_aerosol_strat, new_aod,
    12731277     .     bl95_b0, bl95_b1,
    12741278c     nv flags pour la convection et les poches froides
     
    15951599     &                       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie,
    15961600     &                       read_climoz, phys_out_filestations,
    1597      &                       new_aod, aerosol_couple
    1598      &                        )
     1601     &                       new_aod, aerosol_couple,
     1602     &                       flag_aerosol_strat )
    15991603c$OMP END MASTER
    16001604c$OMP BARRIER
     
    29722976         cg_aero(:,:,:,:)  = 0.
    29732977      ENDIF
     2978c
     2979c--STRAT AEROSOL
     2980c--updates tausum_aero,tau_aero,piz_aero,cg_aero
     2981      IF (flag_aerosol_strat) THEN
     2982         PRINT *,'appel a readaerosolstrat', mth_cur
     2983         CALL readaerosolstrato(debut)
     2984      ENDIF
     2985c--fin STRAT AEROSOL
    29742986
    29752987cIM calcul nuages par le simulateur ISCCP
     
    33593371     e        t_seri,q_seri,wo,
    33603372     e        cldfrarad, cldemirad, cldtaurad,
    3361      e        ok_ade, ok_aie, flag_aerosol,
     3373     e        ok_ade.OR.flag_aerosol_strat, ok_aie, flag_aerosol,
     3374     e        flag_aerosol_strat,
    33623375     e        tau_aero, piz_aero, cg_aero,
    33633376     e        cldtaupirad,new_aod,
     
    34013414     e        t_seri,q_seri,wo,
    34023415     e        cldfra, cldemi, cldtau,
    3403      e        ok_ade, ok_aie, flag_aerosol,
     3416     e        ok_ade.OR.flag_aerosol_strat, ok_aie, flag_aerosol,
     3417     e        flag_aerosol_strat,
    34043418     e        tau_aero, piz_aero, cg_aero,
    34053419     e        cldtaupi,new_aod,
  • LMDZ5/trunk/libf/phylmd/radlwsw_m.F90

    r1687 r1764  
    1111   cldfra, cldemi, cldtaupd,&
    1212   ok_ade, ok_aie, flag_aerosol,&
     13   flag_aerosol_strat,&
    1314   tau_aero, piz_aero, cg_aero,&
    1415   cldtaupi, new_aod, &
     
    5758  ! ok_aie---input-L- apply the Aerosol Indirect Effect or not?
    5859  ! flag_aerosol-input-I- aerosol flag from 0 to 6
     60  ! flag_aerosol_strat-input-I- use stratospheric aerosols flag (T/F)
    5961  ! tau_ae, piz_ae, cg_ae-input-R- aerosol optical properties (calculated in aeropt.F)
    6062  ! cldtaupi-input-R- epaisseur optique des nuages dans le visible
     
    121123  LOGICAL, INTENT(in)  :: ok_ade, ok_aie                                 ! switches whether to use aerosol direct (indirect) effects or not
    122124  INTEGER, INTENT(in)  :: flag_aerosol                                   ! takes value 0 (no aerosol) or 1 to 6 (aerosols)
     125  LOGICAL, INTENT(in)  :: flag_aerosol_strat                             ! use stratospheric aerosols
    123126  REAL,    INTENT(in)  :: cldfra(KLON,KLEV), cldemi(KLON,KLEV), cldtaupd(KLON,KLEV)
    124127  REAL,    INTENT(in)  :: tau_aero(KLON,KLEV,9,2)                        ! aerosol optical properties (see aeropt.F)
     
    360363               ztopswadaero,zsolswadaero,&
    361364               ztopswaiaero,zsolswaiaero,&
    362                ok_ade, ok_aie, flag_aerosol)
     365               ok_ade, ok_aie)
    363366         
    364367       ELSE ! new_aod=T         
     
    379382               zsolsw_aero,zsolsw0_aero,&
    380383               ztopswcf_aero,zsolswcf_aero, &
    381                ok_ade, ok_aie, flag_aerosol)
     384               ok_ade, ok_aie, flag_aerosol,flag_aerosol_strat)
    382385       ENDIF
    383386
  • LMDZ5/trunk/libf/phylmd/sw_aeroAR4.F90

    r1667 r1764  
    1818     PSOLSWAERO,PSOLSW0AERO,&
    1919     PTOPSWCFAERO,PSOLSWCFAERO,&
    20      ok_ade, ok_aie, flag_aerosol )
     20     ok_ade, ok_aie, flag_aerosol, flag_aerosol_strat )
    2121
    2222  USE dimphy
     
    138138
    139139  LOGICAL ok_ade, ok_aie    ! use aerosol forcings or not?
     140  LOGICAL flag_aerosol_strat ! use stratospehric aerosols
    140141  INTEGER flag_aerosol      ! global flag for aerosol 0 (no aerosol) or 1-5 (aerosols)
    141142  REAL(KIND=8) tauaero(kdlon,kflev,9,2)  ! aerosol optical properties
     
    307308     ENDIF ! swaero_diag .or. .not. AEROSOLFEEDBACK_ACTIVE
    308309
    309      IF (flag_aerosol .GT. 0 ) THEN
     310     IF (flag_aerosol .GT. 0 .OR. flag_aerosol_strat) THEN
    310311
    311312     IF (ok_ade.and.swaero_diag .or. .not. ok_ade) THEN
     
    498499     ENDIF ! ok_aie     
    499500
    500      ENDIF !--if flag_aerosol GT 0
     501     ENDIF !--if flag_aerosol GT 0 OR flag_aerosol_strat
    501502
    502503     itapsw = 0
     
    504505  itapsw = itapsw + 1
    505506
    506   IF  ( AEROSOLFEEDBACK_ACTIVE .AND. flag_aerosol .GT. 0 ) THEN
     507  IF  ( AEROSOLFEEDBACK_ACTIVE .AND. (flag_aerosol .GT. 0 .OR. flag_aerosol_strat) ) THEN
    507508  IF ( ok_ade .and. ok_aie  ) THEN
    508509    ZFSUP(:,:) =    ZFSUP_AERO(:,:,4)
Note: See TracChangeset for help on using the changeset viewer.