Changeset 3525


Ignore:
Timestamp:
May 28, 2019, 2:52:20 PM (5 years ago)
Author:
Laurent Fairhead
Message:

Modifs necessaires à la version 6.0.10
OB

Location:
LMDZ6/branches/IPSLCM6.0.15/libf
Files:
1 added
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/IPSLCM6.0.15/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r3519 r3525  
    113113  INTEGER :: flag_aerosol
    114114  INTEGER :: flag_aerosol_strat
     115  LOGICAL :: flag_aer_feedback
    115116  LOGICAL :: flag_bc_internal_mixture
    116117  LOGICAL :: new_aod
     
    134135                   ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan,            &
    135136                   aerosol_couple, chemistry_couple, flag_aerosol,        &
    136                    flag_aerosol_strat, new_aod, flag_bc_internal_mixture, &
     137                   flag_aerosol_strat,                                    &
     138                   flag_aer_feedback,                                     &
     139                   new_aod, flag_bc_internal_mixture,                     &
    137140                   bl95_b0, bl95_b1, read_climoz, alp_offset)
    138141  CALL phys_state_var_init(read_climoz)
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/StratAer/micphy_tstep.F90

    • Property svn:keywords set to Id
    r3098 r3525  
     1!
     2! $Id$
     3!
    14SUBROUTINE micphy_tstep(pdtphys,tr_seri,t_seri,pplay,paprs,rh,is_strato)
    25
     6  USE geometry_mod, ONLY : latitude_deg !NL- latitude corr. to local domain
    37  USE dimphy, ONLY : klon,klev
    48  USE aerophys
     
    913  USE sulfate_aer_mod, ONLY : STRAACT
    1014  USE YOMCST, ONLY : RPI, RD, RG
    11 
     15  USE print_control_mod, ONLY: lunout
     16  USE strataer_mod
     17 
    1218  IMPLICIT NONE
    1319
     
    8995      ! compute nucleation rate in kg(H2SO4)/kgA/s
    9096      CALL nucleation_rate(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev),rh(ilon,ilev), &
    91              & a_xm,b_xm,c_xm,nucl_rate,ntot,x)
     97           & a_xm,b_xm,c_xm,nucl_rate,ntot,x)
     98      !NL - add nucleation box (if flag on)
     99      IF (flag_nuc_rate_box) THEN
     100         IF (latitude_deg(ilon).LE.(nuclat_min) .OR. latitude_deg(ilon).GE.(nuclat_max) &
     101              .OR. pplay(ilon,ilev).GE.nucpres_max .AND. pplay(ilon,ilev) .LE. nucpres_min ) THEN
     102            nucl_rate=0.0
     103         ENDIF
     104      ENDIF
    92105      ! compute cond/evap rate in kg(H2SO4)/kgA/s
    93106      CALL condens_evapor_rate(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), &
     
    160173    DO it=1, nbtr
    161174      IF (tr_seri(ilon,ilev,it).LT.0.0) THEN
    162         PRINT *, 'micphy_tstep: negative concentration', tr_seri(ilon,ilev,it), ilon, ilev, it
     175         WRITE(lunout,*) 'micphy_tstep: negative concentration', tr_seri(ilon,ilev,it), ilon, ilev, it
    163176      ENDIF
    164177    ENDDO
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/StratAer/traccoag_mod.F90

    • Property svn:keywords set to Id
    r3114 r3525  
     1!
     2! $Id$
     3!
    14MODULE traccoag_mod
    25!
     
    1619    USE infotrac
    1720    USE aerophys
    18     USE geometry_mod, ONLY : cell_area
     21    USE geometry_mod, ONLY : cell_area, boundslat
    1922    USE mod_grid_phy_lmdz
    2023    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
     
    2427    USE phys_local_var_mod, ONLY: stratomask
    2528    USE YOMCST
     29    USE print_control_mod, ONLY: lunout
     30    USE strataer_mod
     31    USE phys_cal_mod, ONLY : year_len
    2632
    2733    IMPLICIT NONE
     
    5258! Local variables
    5359!----------------
    54 ! flag for sulfur emission scenario: (0) background aerosol ; (1) volcanic eruption ; (2) stratospheric aerosol injections (SAI)
    55     INTEGER,PARAMETER  :: flag_sulf_emit=2
    56 !
    57 !--flag_sulf_emit=1 --example Pinatubo
    58     INTEGER,PARAMETER :: year_emit_vol=1991          ! year of emission date
    59     INTEGER,PARAMETER :: mth_emit_vol=6              ! month of emission date
    60     INTEGER,PARAMETER :: day_emit_vol=15             ! day of emission date
    61     REAL,PARAMETER    :: m_aer_emiss_vol=7.e9   ! emitted sulfur mass in kgS, e.g. 7Tg(S)=14Tg(SO2)
    62     REAL,PARAMETER    :: altemiss_vol=17.e3     ! emission altitude in m
    63     REAL,PARAMETER    :: sigma_alt_vol=1.e3     ! standard deviation of emission altitude in m
    64     REAL,PARAMETER    :: xlat_vol=15.14         ! latitude of volcano in degree
    65     REAL,PARAMETER    :: xlon_vol=120.35        ! longitude of volcano in degree
    66 
    67 !--flag_sulf_emit=2 --SAI
    68     REAL,PARAMETER    :: m_aer_emiss_sai=1.e10  ! emitted sulfur mass in kgS, eg 1e9=1TgS, 1e10=10TgS
    69     REAL,PARAMETER    :: altemiss_sai=17.e3     ! emission altitude in m
    70     REAL,PARAMETER    :: sigma_alt_sai=1.e3     ! standard deviation of emission altitude in m
    71     REAL,PARAMETER    :: xlat_sai=0.01          ! latitude of SAI in degree
    72     REAL,PARAMETER    :: xlon_sai=120.35        ! longitude of SAI in degree
    73 
    74 !--other local variables
    75     INTEGER                                :: it, k, i, ilon, ilev, itime, i_int
     60    REAL                                   :: m_aer_emiss_vol_daily ! daily injection mass emission
     61    REAL                                   :: sum_emi_so2         ! Test sum of all LON for budg_emi_so2
     62    INTEGER                                :: it, k, i, ilon, ilev, itime, i_int, ieru
    7663    LOGICAL,DIMENSION(klon,klev)           :: is_strato           ! true = above tropopause, false = below
    7764    REAL,DIMENSION(klon,klev)              :: m_air_gridbox       ! mass of air in every grid box [kg]
     
    9077    REAL,DIMENSION(klev)                   :: zdm                 ! mass of atm. model layer in kg
    9178    REAL,DIMENSION(klon,klev)              :: dens_aer            ! density of aerosol particles [kg/m3 aerosol] with default H2SO4 mass fraction
    92     REAL                                   :: dlat, dlon          ! d latitude and d longitude of grid in degree
    9379    REAL                                   :: emission            ! emission
     80    REAL                                   :: theta_min, theta_max ! for SAI computation between two latitudes
     81    REAL                                   :: dlat_loc
    9482
    9583    IF (is_mpi_root) THEN
    96       PRINT *,'in traccoag: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
     84       WRITE(lunout,*) 'in traccoag: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
     85       WRITE(lunout,*) 'IN traccoag flag_sulf_emit: ',flag_sulf_emit
     86       IF (flag_sulf_emit == 1) THEN
     87          WRITE(lunout,*) 'IN traccoag nErupt: ',nErupt
     88          WRITE(lunout,*) 'IN traccoag injdur: ',injdur
     89          WRITE(lunout,*) 'IN traccoag : year_emit_vol',year_emit_vol
     90          WRITE(lunout,*) 'IN traccoag : mth_emit_vol',mth_emit_vol
     91          WRITE(lunout,*) 'IN traccoag : day_emit_vol',day_emit_vol
     92          WRITE(lunout,*) 'IN traccoag : m_aer_emiss_vol',m_aer_emiss_vol
     93          WRITE(lunout,*) 'IN traccoag : altemiss_vol',altemiss_vol
     94          WRITE(lunout,*) 'IN traccoag : sigma_alt_vol',sigma_alt_vol
     95          WRITE(lunout,*) 'IN traccoag : ponde_lonlat_vol',ponde_lonlat_vol
     96          WRITE(lunout,*) 'IN traccoag : xlat_min_vol',xlat_min_vol
     97          WRITE(lunout,*) 'IN traccoag : xlat_max_vol',xlat_max_vol
     98          WRITE(lunout,*) 'IN traccoag : xlon_min_vol',xlon_min_vol
     99          WRITE(lunout,*) 'IN traccoag : xlon_max_vol',xlon_max_vol
     100       ELSEIF (flag_sulf_emit == 2) THEN
     101          WRITE(lunout,*) 'IN traccoag : m_aer_emiss_sai',m_aer_emiss_sai
     102          WRITE(lunout,*) 'IN traccoag : altemiss_sai',altemiss_sai
     103          WRITE(lunout,*) 'IN traccoag : sigma_alt_sai',sigma_alt_sai
     104          WRITE(lunout,*) 'IN traccoag : xlat_sai',xlat_sai
     105          WRITE(lunout,*) 'IN traccoag : xlon_sai',xlon_sai
     106       ELSEIF (flag_sulf_emit == 3) THEN
     107          WRITE(lunout,*) 'IN traccoag : m_aer_emiss_sai',m_aer_emiss_sai
     108          WRITE(lunout,*) 'IN traccoag : altemiss_sai',altemiss_sai
     109          WRITE(lunout,*) 'IN traccoag : sigma_alt_sai',sigma_alt_sai
     110          WRITE(lunout,*) 'IN traccoag : xlat_min_sai',xlat_min_sai
     111          WRITE(lunout,*) 'IN traccoag : xlat_max_sai',xlat_max_sai
     112          WRITE(lunout,*) 'IN traccoag : xlon_sai',xlon_sai
     113       ENDIF
     114       WRITE(lunout,*) 'IN traccoag : flag_nuc_rate_box = ',flag_nuc_rate_box
     115       IF (flag_nuc_rate_box) THEN
     116          WRITE(lunout,*) 'IN traccoag : nuclat_min = ',nuclat_min,', nuclat_max = ',nuclat_max
     117          WRITE(lunout,*) 'IN traccoag : nucpres_min = ',nucpres_min,', nucpres_max = ',nucpres_max
     118       ENDIF
    97119    ENDIF
    98 
    99     dlat=180./2./FLOAT(nbp_lat)   ! d latitude in degree
    100     dlon=360./2./FLOAT(nbp_lon)   ! d longitude in degree
    101 
     120   
    102121    DO it=1, nbtr_bin
    103122      r_bin(it)=mdw(it)/2.
     
    120139    IF (debutphy .and. is_mpi_root) THEN
    121140      DO it=1, nbtr_bin
    122         PRINT *,'radius bin', it, ':', r_bin(it), '(from',  r_lower(it), 'to', r_upper(it), ')'
     141        WRITE(lunout,*) 'radius bin', it, ':', r_bin(it), '(from',  r_lower(it), 'to', r_upper(it), ')'
    123142      ENDDO
    124143    ENDIF
     
    170189      !--only emit on day of eruption
    171190      ! stretch emission over one day of Pinatubo eruption
    172       IF (year_cur==year_emit_vol.AND.mth_cur==mth_emit_vol.AND.day_cur==day_emit_vol) THEN
    173 !
    174         DO i=1,klon
    175           !Pinatubo eruption at 15.14N, 120.35E
    176           IF  ( xlat(i).GE.xlat_vol-dlat .AND. xlat(i).LT.xlat_vol+dlat .AND. &
    177                 xlon(i).GE.xlon_vol-dlon .AND. xlon(i).LT.xlon_vol+dlon ) THEN
    178 !
    179           PRINT *,'coordinates of volcanic injection point=',xlat(i), xlon(i), day_cur, mth_cur, year_cur
    180 !         compute altLMDz
    181             altLMDz(:)=0.0
    182             DO k=1, klev
    183               zrho=pplay(i,k)/t_seri(i,k)/RD       !air density in kg/m3
    184               zdm(k)=(paprs(i,k)-paprs(i,k+1))/RG  !mass of layer in kg
    185               zdz=zdm(k)/zrho                      !thickness of layer in m
    186               altLMDz(k+1)=altLMDz(k)+zdz          !altitude of interface
    187             ENDDO
    188             !compute distribution of emission to vertical model layers (based on Gaussian peak in altitude)
    189             f_lay_sum=0.0
    190             DO k=1, klev
    191               f_lay_emiss(k)=0.0
    192               DO i_int=1, n_int_alt
    193                 alt=altLMDz(k)+float(i_int)*(altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
    194                 f_lay_emiss(k)=f_lay_emiss(k)+1./(sqrt(2.*RPI)*sigma_alt_vol)* &
    195                 &              exp(-0.5*((alt-altemiss_vol)/sigma_alt_vol)**2.)*   &
    196                 &              (altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
    197               ENDDO
    198               f_lay_sum=f_lay_sum+f_lay_emiss(k)
    199             ENDDO
    200             !correct for step integration error
    201             f_lay_emiss(:)=f_lay_emiss(:)/f_lay_sum
    202             !emission as SO2 gas (with m(SO2)=64/32*m_aer_emiss)
    203             !vertically distributed emission
    204             DO k=1, klev
    205               ! stretch emission over one day (minus one timestep) of Pinatubo eruption
    206               emission=m_aer_emiss_vol*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/1./(86400.-pdtphys)
    207               tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
    208               budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
    209             ENDDO
    210           ENDIF ! emission grid cell
    211         ENDDO ! klon loop
    212       ENDIF ! emission period
    213 
     191       DO ieru=1, nErupt
     192          IF (is_mpi_root) THEN
     193             sum_emi_so2 = 0.0 ! Init sum
     194          ENDIF
     195          IF (year_cur==year_emit_vol(ieru).AND.mth_cur==mth_emit_vol(ieru).AND.&
     196               day_cur>=day_emit_vol(ieru).AND.day_cur<(day_emit_vol(ieru)+injdur)) THEN
     197             !
     198             ! daily injection mass emission - NL
     199             m_aer_emiss_vol_daily = m_aer_emiss_vol(ieru)/(REAL(injdur)*REAL(ponde_lonlat_vol(ieru)))
     200             WRITE(lunout,*) 'IN traccoag DD m_aer_emiss_vol(ieru)=',m_aer_emiss_vol(ieru), &
     201                  'ponde_lonlat_vol(ieru)=',ponde_lonlat_vol(ieru),'(injdur*ponde_lonlat_vol(ieru))', &
     202                  (injdur*ponde_lonlat_vol(ieru)),'m_aer_emiss_vol_daily=',m_aer_emiss_vol_daily,'ieru=',ieru
     203             WRITE(lunout,*) 'IN traccoag, dlon=',dlon
     204             DO i=1,klon
     205                !Pinatubo eruption at 15.14N, 120.35E
     206                dlat_loc=180./RPI/2.*(boundslat(i,1)-boundslat(i,3)) ! dlat = half difference of boundary latitudes
     207                WRITE(lunout,*) 'IN traccoag, dlat=',dlat_loc
     208                IF ( xlat(i).GE.xlat_min_vol(ieru)-dlat_loc .AND. xlat(i).LT.xlat_max_vol(ieru)+dlat_loc .AND. &
     209                     xlon(i).GE.xlon_min_vol(ieru)-dlon .AND. xlon(i).LT.xlon_max_vol(ieru)+dlon ) THEN
     210                   !
     211                   WRITE(lunout,*) 'coordinates of volcanic injection point=',xlat(i),xlon(i),day_cur,mth_cur,year_cur
     212                   WRITE(lunout,*) 'DD m_aer_emiss_vol_daily=',m_aer_emiss_vol_daily
     213                   !         compute altLMDz
     214                   altLMDz(:)=0.0
     215                   DO k=1, klev
     216                      zrho=pplay(i,k)/t_seri(i,k)/RD       !air density in kg/m3
     217                      zdm(k)=(paprs(i,k)-paprs(i,k+1))/RG  !mass of layer in kg
     218                      zdz=zdm(k)/zrho                      !thickness of layer in m
     219                      altLMDz(k+1)=altLMDz(k)+zdz          !altitude of interface
     220                   ENDDO
     221
     222                   SELECT CASE(flag_sulf_emit_distrib)
     223                   
     224                   CASE(0) ! Gaussian distribution
     225                   !compute distribution of emission to vertical model layers (based on Gaussian peak in altitude)
     226                   f_lay_sum=0.0
     227                   DO k=1, klev
     228                      f_lay_emiss(k)=0.0
     229                      DO i_int=1, n_int_alt
     230                         alt=altLMDz(k)+float(i_int)*(altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     231                         f_lay_emiss(k)=f_lay_emiss(k)+1./(sqrt(2.*RPI)*sigma_alt_vol(ieru))* &
     232                              &              exp(-0.5*((alt-altemiss_vol(ieru))/sigma_alt_vol(ieru))**2.)*   &
     233                              &              (altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     234                      ENDDO
     235                      f_lay_sum=f_lay_sum+f_lay_emiss(k)
     236                   ENDDO
     237                   
     238                   CASE(1) ! Uniform distribution
     239                   ! In this case, parameter sigma_alt_vol(ieru) is considered to be half the
     240                   ! height of the injection, centered around altemiss_vol(ieru)
     241                   DO k=1, klev
     242                      f_lay_emiss(k)=max(min(altemiss_vol(ieru)+sigma_alt_vol(ieru),altLMDz(k+1))- &
     243                      & max(altemiss_vol(ieru)-sigma_alt_vol(ieru),altLMDz(k)),0.)/(2.*sigma_alt_vol(ieru))
     244                      f_lay_sum=f_lay_sum+f_lay_emiss(k)
     245                   ENDDO
     246
     247                   END SELECT        ! End CASE over flag_sulf_emit_distrib)
     248
     249                   WRITE(lunout,*) "IN traccoag m_aer_emiss_vol=",m_aer_emiss_vol(ieru)
     250                   WRITE(lunout,*) "IN traccoag f_lay_emiss=",f_lay_emiss
     251                   !correct for step integration error
     252                   f_lay_emiss(:)=f_lay_emiss(:)/f_lay_sum
     253                   !emission as SO2 gas (with m(SO2)=64/32*m_aer_emiss)
     254                   !vertically distributed emission
     255                   DO k=1, klev
     256                      ! stretch emission over one day of Pinatubo eruption
     257                      emission=m_aer_emiss_vol_daily*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/1./(86400.-pdtphys)
     258                      tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
     259                      budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
     260                   ENDDO
     261                   sum_emi_so2 = sum_emi_so2 + budg_emi_so2(i) ! Sum all LON
     262                ENDIF ! emission grid cell
     263             ENDDO ! klon loop
     264             WRITE(lunout,*) "IN traccoag (ieru=",ieru,") global sum_emi_so2=",sum_emi_so2
     265             WRITE(lunout,*) "IN traccoag (ieru=",ieru,") m_aer_emiss_vol_daily=",m_aer_emiss_vol_daily
     266          ENDIF ! emission period
     267       ENDDO ! eruption number
     268       
    214269    CASE(2) ! stratospheric aerosol injections (SAI)
    215270!
     
    217272!       SAI standard scenario with continuous emission from 1 grid point at the equator
    218273!       SAI emission on single month
    219 !       IF  ((mth_cur==4 .AND. &
    220274!       SAI continuous emission o
    221         IF  ( xlat(i).GE.xlat_sai-dlat .AND. xlat(i).LT.xlat_sai+dlat .AND. &
     275        dlat_loc=180./RPI/2.*(boundslat(i,1)-boundslat(i,3)) ! dlat = half difference of boundary latitudes
     276        WRITE(lunout,*) "IN traccoag, dlon=",dlon
     277        WRITE(lunout,*) "IN traccoag, dlat=",dlat_loc
     278        IF  ( xlat(i).GE.xlat_sai-dlat_loc .AND. xlat(i).LT.xlat_sai+dlat_loc .AND. &
    222279          &   xlon(i).GE.xlon_sai-dlon .AND. xlon(i).LT.xlon_sai+dlon ) THEN
    223280!
    224           PRINT *,'coordinates of SAI point=',xlat(i), xlon(i), day_cur, mth_cur, year_cur
     281          WRITE(lunout,*) 'coordinates of SAI point=',xlat(i), xlon(i), day_cur, mth_cur, year_cur
    225282!         compute altLMDz
    226283          altLMDz(:)=0.0
     
    231288            altLMDz(k+1)=altLMDz(k)+zdz          !altitude of interface
    232289          ENDDO
     290
     291          SELECT CASE(flag_sulf_emit_distrib)
     292
     293          CASE(0) ! Gaussian distribution
    233294          !compute distribution of emission to vertical model layers (based on Gaussian peak in altitude)
    234295          f_lay_sum=0.0
    235           DO k=1, klev
    236             f_lay_emiss(k)=0.0
    237             DO i_int=1, n_int_alt
    238               alt=altLMDz(k)+float(i_int)*(altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
    239               f_lay_emiss(k)=f_lay_emiss(k)+1./(sqrt(2.*RPI)*sigma_alt_sai)* &
    240               &              exp(-0.5*((alt-altemiss_sai)/sigma_alt_sai)**2.)*   &
    241               &              (altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
    242             ENDDO
    243             f_lay_sum=f_lay_sum+f_lay_emiss(k)
    244           ENDDO
     296               DO k=1, klev
     297                     f_lay_emiss(k)=0.0
     298                     DO i_int=1, n_int_alt
     299                         alt=altLMDz(k)+float(i_int)*(altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     300                         f_lay_emiss(k)=f_lay_emiss(k)+1./(sqrt(2.*RPI)*sigma_alt_sai)* &
     301                         &              exp(-0.5*((alt-altemiss_sai)/sigma_alt_sai)**2.)*   &
     302                         &              (altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     303                     ENDDO
     304                     f_lay_sum=f_lay_sum+f_lay_emiss(k)
     305               ENDDO
     306
     307          CASE(1) ! Uniform distribution
     308          f_lay_sum=0.0
     309          ! In this case, parameter sigma_alt_vol(ieru) is considered to be half
     310          ! the height of the injection, centered around altemiss_sai
     311               DO k=1, klev
     312                    f_lay_emiss(k)=max(min(altemiss_sai+sigma_alt_sai,altLMDz(k+1))- &
     313                    & max(altemiss_sai-sigma_alt_sai,altLMDz(k)),0.)/(2.*sigma_alt_sai)
     314                    f_lay_sum=f_lay_sum+f_lay_emiss(k)
     315               ENDDO
     316
     317          END SELECT ! Gaussian or uniform distribution
     318
    245319          !correct for step integration error
    246320          f_lay_emiss(:)=f_lay_emiss(:)/f_lay_sum
     
    249323          DO k=1, klev
    250324            ! stretch emission over whole year (360d)
    251             emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/360./86400. 
     325            emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/year_len/86400. 
    252326            tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
    253327            budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
    254328          ENDDO
     329
    255330!          !emission as monodisperse particles with 0.1um dry radius (BIN21)
    256331!          !vertically distributed emission
    257332!          DO k=1, klev
    258333!            ! stretch emission over whole year (360d)
    259 !            emission=m_aer_emiss*(mH2SO4mol/mSatom)/m_part_dry(21)/m_air_gridbox(i,k)*f_lay_emiss(k)/360./86400
     334!            emission=m_aer_emiss*(mH2SO4mol/mSatom)/m_part_dry(21)/m_air_gridbox(i,k)*f_lay_emiss(k)/year_len/86400
     335!            tr_seri(i,k,id_BIN01_strat+20)=tr_seri(i,k,id_BIN01_strat+20)+emission*pdtphys
     336!            budg_emi_part(i)=budg_emi_part(i)+emission*zdm(k)*mSatom/mH2SO4mol
     337!          ENDDO
     338        ENDIF ! emission grid cell
     339      ENDDO ! klon loop
     340
     341    CASE(3) ! --- SAI injection over a single band of longitude and between
     342            !     lat_min and lat_max
     343
     344    WRITE(lunout,*) 'IN traccoag, dlon=',dlon
     345    DO i=1,klon
     346!       SAI scenario with continuous emission
     347        dlat_loc=180./RPI/2.*(boundslat(i,1)-boundslat(i,3)) ! dlat = half difference of boundary latitudes
     348        WRITE(lunout,*) 'IN traccoag, dlat = ',dlat_loc
     349        theta_min = max(xlat(i)-dlat_loc,xlat_min_sai)
     350        theta_max = min(xlat(i)+dlat_loc,xlat_max_sai)
     351        IF  ( xlat(i).GE.xlat_min_sai-dlat_loc .AND. xlat(i).LT.xlat_max_sai+dlat_loc .AND. &
     352          &   xlon(i).GE.xlon_sai-dlon .AND. xlon(i).LT.xlon_sai+dlon ) THEN
     353!
     354!         compute altLMDz
     355          altLMDz(:)=0.0
     356          DO k=1, klev
     357            zrho=pplay(i,k)/t_seri(i,k)/RD       !air density in kg/m3
     358            zdm(k)=(paprs(i,k)-paprs(i,k+1))/RG  !mass of layer in kg
     359            zdz=zdm(k)/zrho                      !thickness of layer in m
     360            altLMDz(k+1)=altLMDz(k)+zdz          !altitude of interface
     361          ENDDO
     362
     363          SELECT CASE(flag_sulf_emit_distrib)
     364
     365          CASE(0) ! Gaussian distribution
     366          !compute distribution of emission to vertical model layers (based on
     367          !Gaussian peak in altitude)
     368          f_lay_sum=0.0
     369               DO k=1, klev
     370                     f_lay_emiss(k)=0.0
     371                     DO i_int=1, n_int_alt
     372                         alt=altLMDz(k)+float(i_int)*(altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     373                         f_lay_emiss(k)=f_lay_emiss(k)+1./(sqrt(2.*RPI)*sigma_alt_sai)* &
     374                         & exp(-0.5*((alt-altemiss_sai)/sigma_alt_sai)**2.)*   &
     375                         & (altLMDz(k+1)-altLMDz(k))/float(n_int_alt)
     376                     ENDDO
     377                     f_lay_sum=f_lay_sum+f_lay_emiss(k)
     378               ENDDO
     379
     380          CASE(1) ! Uniform distribution
     381          f_lay_sum=0.0
     382          ! In this case, parameter sigma_alt_vol(ieru) is considered to be half
     383          ! the height of the injection, centered around altemiss_sai
     384               DO k=1, klev
     385                    f_lay_emiss(k)=max(min(altemiss_sai+sigma_alt_sai,altLMDz(k+1))- &
     386                    & max(altemiss_sai-sigma_alt_sai,altLMDz(k)),0.)/(2.*sigma_alt_sai)
     387                    f_lay_sum=f_lay_sum+f_lay_emiss(k)
     388               ENDDO
     389
     390          END SELECT ! Gaussian or uniform distribution
     391
     392          !correct for step integration error
     393          f_lay_emiss(:)=f_lay_emiss(:)/f_lay_sum
     394          !emission as SO2 gas (with m(SO2)=64/32*m_aer_emiss)
     395          !vertically distributed emission
     396          DO k=1, klev
     397            ! stretch emission over whole year (360d)
     398            emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/ &
     399                      & year_len/86400.*(sin(theta_max/180.*RPI)-sin(theta_min/180.*RPI))/ &
     400                      & (sin(xlat_max_sai/180.*RPI)-sin(xlat_min_sai/180.*RPI))
     401            tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
     402            budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
     403          ENDDO
     404
     405!          !emission as monodisperse particles with 0.1um dry radius (BIN21)
     406!          !vertically distributed emission
     407!          DO k=1, klev
     408!            ! stretch emission over whole year (360d)
     409!            emission=m_aer_emiss*(mH2SO4mol/mSatom)/m_part_dry(21)/m_air_gridbox(i,k)*f_lay_emiss(k)/year_len/86400
    260410!            tr_seri(i,k,id_BIN01_strat+20)=tr_seri(i,k,id_BIN01_strat+20)+emission*pdtphys
    261411!            budg_emi_part(i)=budg_emi_part(i)+emission*zdm(k)*mSatom/mH2SO4mol
     
    291441        IF (mdw(it) .LT. 2.5e-6) THEN
    292442          !surf_PM25_sulf(i)=surf_PM25_sulf(i)+tr_seri(i,1,it+nbtr_sulgas)*m_part(i,1,it) &
    293           !assume that particles consist of ammonium sulfate at the surface (132g/mol) and are dry at T = 20 deg. C and 50 perc. humidity
     443          !assume that particles consist of ammonium sulfate at the surface (132g/mol)
     444          !and are dry at T = 20 deg. C and 50 perc. humidity
    294445          surf_PM25_sulf(i)=surf_PM25_sulf(i)+tr_seri(i,1,it+nbtr_sulgas) &
    295446                           & *132./98.*dens_aer_dry*4./3.*RPI*(mdw(it)/2.)**3 &
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/conf_phys_m.F90

    r3408 r3525  
    1818       iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    1919       ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, aerosol_couple, &
    20        chemistry_couple, flag_aerosol, flag_aerosol_strat, new_aod, &
     20       chemistry_couple, flag_aerosol, flag_aerosol_strat,         &
     21       flag_aer_feedback, new_aod, &
    2122       flag_bc_internal_mixture, bl95_b0, bl95_b1,&
    2223       read_climoz, &
     
    3031    USE print_control_mod, ONLY: lunout
    3132
    32     include "conema3.h"
    33     include "fisrtilp.h"
    34     include "nuage.h"
    35     include "YOMCST.h"
    36     include "YOMCST2.h"
    37 
    38     include "thermcell.h"
    39 
     33    INCLUDE "conema3.h"
     34    INCLUDE "fisrtilp.h"
     35    INCLUDE "nuage.h"
     36    INCLUDE "YOMCST.h"
     37    INCLUDE "YOMCST2.h"
     38    INCLUDE "thermcell.h"
    4039
    4140    !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
    42     include "clesphys.h"
    43     include "compbl.h"
    44     include "comsoil.h"
    45     include "YOEGWD.h"
     41    INCLUDE "clesphys.h"
     42    INCLUDE "compbl.h"
     43    INCLUDE "comsoil.h"
     44    INCLUDE "YOEGWD.h"
    4645    !
    4746    ! Configuration de la "physique" de LMDZ a l'aide de la fonction
     
    4948    !
    5049    ! LF 05/2001
    51     !
    52 
    5350    !
    5451    ! type_ocean:      type d'ocean (force, slab, couple)
     
    8077    INTEGER              :: flag_aerosol
    8178    INTEGER              :: flag_aerosol_strat
     79    LOGICAL              :: flag_aer_feedback
    8280    LOGICAL              :: flag_bc_internal_mixture
    8381    LOGICAL              :: new_aod
     
    10199    INTEGER, SAVE       :: flag_aerosol_omp
    102100    INTEGER, SAVE       :: flag_aerosol_strat_omp
     101    LOGICAL, SAVE       :: flag_aer_feedback_omp
    103102    LOGICAL, SAVE       :: flag_bc_internal_mixture_omp
    104103    LOGICAL, SAVE       :: new_aod_omp
     
    10511050    ENDIF
    10521051
    1053     !
     1052    !Config Key  = flag_aer_feedback
     1053    !Config Desc = (des)activate aerosol radiative feedback
     1054    ! - F = no aerosol radiative feedback
     1055    ! - T = aerosol radiative feedback
     1056    !Config Def  = T
     1057    !Config Help = Used in physiq.F
     1058    !
     1059    flag_aer_feedback_omp = .TRUE.
     1060    IF (iflag_rrtm_omp==1) THEN
     1061       CALL getin('flag_aer_feedback',flag_aer_feedback_omp)
     1062    ENDIF
     1063
    10541064    !Config Key  = iflag_cld_th
    10551065    !Config Desc = 
     
    22982308    flag_aerosol=flag_aerosol_omp
    22992309    flag_aerosol_strat=flag_aerosol_strat_omp
     2310    flag_aer_feedback=flag_aer_feedback_omp
    23002311    flag_bc_internal_mixture=flag_bc_internal_mixture_omp
    23012312    new_aod=new_aod_omp
     
    25222533    !$OMP MASTER
    25232534
    2524     write(lunout,*)' ##############################################'
    2525     write(lunout,*)' Configuration des parametres de la physique: '
    2526     write(lunout,*)' Type ocean = ', type_ocean
    2527     write(lunout,*)' Version ocean = ', version_ocean
    2528     write(lunout,*)' Config veget = ', ok_veget,type_veget
    2529     write(lunout,*)' Snow model SISVAT : ok_snow = ', ok_snow
    2530     write(lunout,*)' Config xml pour XIOS : ok_all_xml = ', ok_all_xml
    2531     write(lunout,*)' Sortie journaliere = ', ok_journe
    2532     write(lunout,*)' Sortie haute frequence = ', ok_hf
    2533     write(lunout,*)' Sortie mensuelle = ', ok_mensuel
    2534     write(lunout,*)' Sortie instantanee = ', ok_instan
    2535     write(lunout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
    2536     write(lunout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
    2537     write(lunout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
    2538     write(lunout,*)' Frequence appel simulateur AIRS, freq_AIRS =', freq_AIRS
    2539     write(lunout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
    2540     write(lunout,*)' Excentricite = ',R_ecc
    2541     write(lunout,*)' Equinoxe = ',R_peri
    2542     write(lunout,*)' Inclinaison =',R_incl
    2543     write(lunout,*)' Constante solaire =',solaire
    2544     write(lunout,*)' ok_suntime_rrtm =',ok_suntime_rrtm
    2545     write(lunout,*)' co2_ppm =',co2_ppm
    2546     write(lunout,*)' RCO2_act = ',RCO2_act
    2547     write(lunout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
    2548     write(lunout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
    2549     write(lunout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
    2550     write(lunout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
    2551     write(lunout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
    2552     write(lunout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
    2553     write(lunout,*)' RCFC12_per = ',RCFC12_per
    2554     write(lunout,*)' cvl_comp_threshold=', cvl_comp_threshold
    2555     write(lunout,*)' cvl_sig2feed=', cvl_sig2feed
    2556     write(lunout,*)' cvl_corr=', cvl_corr
    2557     write(lunout,*)'ok_lic_melt=', ok_lic_melt
    2558     write(lunout,*)'ok_lic_cond=', ok_lic_cond
    2559     write(lunout,*)'iflag_cycle_diurne=',iflag_cycle_diurne
    2560     write(lunout,*)'soil_model=',soil_model
    2561     write(lunout,*)'new_oliq=',new_oliq
    2562     write(lunout,*)'ok_orodr=',ok_orodr
    2563     write(lunout,*)'ok_orolf=',ok_orolf
    2564     write(lunout,*)'ok_limitvrai=',ok_limitvrai
    2565     write(lunout,*)'nbapp_rad=',nbapp_rad
    2566     write(lunout,*)'iflag_con=',iflag_con
    2567     write(lunout,*)'nbapp_cv=',nbapp_cv
    2568     write(lunout,*)'nbapp_wk=',nbapp_wk
    2569     write(lunout,*)'iflag_ener_conserv=',iflag_ener_conserv
    2570     write(lunout,*)'ok_conserv_q=',ok_conserv_q
    2571     write(lunout,*)'iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
    2572     write(lunout,*)'iflag_bergeron=',iflag_bergeron
    2573     write(lunout,*)' epmax = ', epmax
    2574     write(lunout,*)' coef_epmax_cape = ', coef_epmax_cape
    2575     write(lunout,*)' ok_adj_ema = ', ok_adj_ema
    2576     write(lunout,*)' iflag_clw = ', iflag_clw
    2577     write(lunout,*)' cld_lc_lsc = ', cld_lc_lsc
    2578     write(lunout,*)' cld_lc_con = ', cld_lc_con
    2579     write(lunout,*)' cld_tau_lsc = ', cld_tau_lsc
    2580     write(lunout,*)' cld_tau_con = ', cld_tau_con
    2581     write(lunout,*)' ffallv_lsc = ', ffallv_lsc
    2582     write(lunout,*)' ffallv_con = ', ffallv_con
    2583     write(lunout,*)' coef_eva = ', coef_eva
    2584     write(lunout,*)' reevap_ice = ', reevap_ice
    2585     write(lunout,*)' iflag_pdf = ', iflag_pdf
    2586     write(lunout,*)' iflag_cld_th = ', iflag_cld_th
    2587     write(lunout,*)' iflag_cld_cv = ', iflag_cld_cv
    2588     write(lunout,*)' tau_cld_cv = ', tau_cld_cv
    2589     write(lunout,*)' coefw_cld_cv = ', coefw_cld_cv
    2590     write(lunout,*)' iflag_radia = ', iflag_radia
    2591     write(lunout,*)' iflag_rrtm = ', iflag_rrtm
    2592     write(lunout,*)' NSW = ', NSW
    2593     write(lunout,*)' iflag_albedo = ', iflag_albedo !albedo SB
    2594     write(lunout,*)' ok_chlorophyll =',ok_chlorophyll ! albedo SB
    2595     write(lunout,*)' iflag_ratqs = ', iflag_ratqs
    2596     write(lunout,*)' seuil_inversion = ', seuil_inversion
    2597     write(lunout,*)' fact_cldcon = ', fact_cldcon
    2598     write(lunout,*)' facttemps = ', facttemps
    2599     write(lunout,*)' ok_newmicro = ',ok_newmicro
    2600     write(lunout,*)' ratqsbas = ',ratqsbas
    2601     write(lunout,*)' ratqshaut = ',ratqshaut
    2602     write(lunout,*)' tau_ratqs = ',tau_ratqs
    2603     write(lunout,*)' top_height = ',top_height
    2604     write(lunout,*)' rad_froid = ',rad_froid
    2605     write(lunout,*)' rad_chau1 = ',rad_chau1
    2606     write(lunout,*)' rad_chau2 = ',rad_chau2
    2607     write(lunout,*)' t_glace_min = ',t_glace_min
    2608     write(lunout,*)' t_glace_max = ',t_glace_max
    2609     write(lunout,*)' exposant_glace = ',exposant_glace
    2610     write(lunout,*)' iflag_t_glace = ',iflag_t_glace
    2611     write(lunout,*)' iflag_cloudth_vert = ',iflag_cloudth_vert
    2612     write(lunout,*)' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
    2613     write(lunout,*)' iflag_ice_thermo = ',iflag_ice_thermo
    2614     write(lunout,*)' rei_min = ',rei_min
    2615     write(lunout,*)' rei_max = ',rei_max
    2616     write(lunout,*)' overlap = ',overlap
    2617     write(lunout,*)' cdmmax = ',cdmmax
    2618     write(lunout,*)' cdhmax = ',cdhmax
    2619     write(lunout,*)' ksta = ',ksta
    2620     write(lunout,*)' ksta_ter = ',ksta_ter
    2621     write(lunout,*)' f_ri_cd_min = ',f_ri_cd_min
    2622     write(lunout,*)' ok_kzmin = ',ok_kzmin
    2623     write(lunout,*)' pbl_lmixmin_alpha = ',pbl_lmixmin_alpha
    2624     write(lunout,*)' fmagic = ',fmagic
    2625     write(lunout,*)' pmagic = ',pmagic
    2626     write(lunout,*)' ok_ade = ',ok_ade
    2627     write(lunout,*)' ok_volcan = ',ok_volcan
    2628     write(lunout,*)' ok_aie = ',ok_aie
    2629     write(lunout,*)' ok_alw = ',ok_alw
    2630     write(lunout,*)' aerosol_couple = ', aerosol_couple
    2631     write(lunout,*)' chemistry_couple = ', chemistry_couple
    2632     write(lunout,*)' flag_aerosol = ', flag_aerosol
    2633     write(lunout,*)' flag_aerosol_strat= ', flag_aerosol_strat
    2634     write(lunout,*)' new_aod = ', new_aod
    2635     write(lunout,*)' aer_type = ',aer_type
    2636     write(lunout,*)' bl95_b0 = ',bl95_b0
    2637     write(lunout,*)' bl95_b1 = ',bl95_b1
    2638     write(lunout,*)' lev_histhf = ',lev_histhf
    2639     write(lunout,*)' lev_histday = ',lev_histday
    2640     write(lunout,*)' lev_histmth = ',lev_histmth
    2641     write(lunout,*)' lev_histins = ',lev_histins
    2642     write(lunout,*)' lev_histLES = ',lev_histLES
    2643     write(lunout,*)' lev_histdayNMC = ',lev_histdayNMC
    2644     write(lunout,*)' levout_histNMC = ',levout_histNMC
    2645     write(lunout,*)' ok_histNMC = ',ok_histNMC
    2646     write(lunout,*)' freq_outNMC = ',freq_outNMC
    2647     write(lunout,*)' freq_calNMC = ',freq_calNMC
    2648     write(lunout,*)' iflag_pbl = ', iflag_pbl
     2535    WRITE(lunout,*)' ##############################################'
     2536    WRITE(lunout,*)' Configuration des parametres de la physique: '
     2537    WRITE(lunout,*)' Type ocean = ', type_ocean
     2538    WRITE(lunout,*)' Version ocean = ', version_ocean
     2539    WRITE(lunout,*)' Config veget = ', ok_veget,type_veget
     2540    WRITE(lunout,*)' Snow model SISVAT : ok_snow = ', ok_snow
     2541    WRITE(lunout,*)' Config xml pour XIOS : ok_all_xml = ', ok_all_xml
     2542    WRITE(lunout,*)' Sortie journaliere = ', ok_journe
     2543    WRITE(lunout,*)' Sortie haute frequence = ', ok_hf
     2544    WRITE(lunout,*)' Sortie mensuelle = ', ok_mensuel
     2545    WRITE(lunout,*)' Sortie instantanee = ', ok_instan
     2546    WRITE(lunout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
     2547    WRITE(lunout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
     2548    WRITE(lunout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
     2549    WRITE(lunout,*)' Frequence appel simulateur AIRS, freq_AIRS =', freq_AIRS
     2550    WRITE(lunout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
     2551    WRITE(lunout,*)' Excentricite = ',R_ecc
     2552    WRITE(lunout,*)' Equinoxe = ',R_peri
     2553    WRITE(lunout,*)' Inclinaison =',R_incl
     2554    WRITE(lunout,*)' Constante solaire =',solaire
     2555    WRITE(lunout,*)' ok_suntime_rrtm =',ok_suntime_rrtm
     2556    WRITE(lunout,*)' co2_ppm =',co2_ppm
     2557    WRITE(lunout,*)' RCO2_act = ',RCO2_act
     2558    WRITE(lunout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
     2559    WRITE(lunout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
     2560    WRITE(lunout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
     2561    WRITE(lunout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
     2562    WRITE(lunout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
     2563    WRITE(lunout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
     2564    WRITE(lunout,*)' RCFC12_per = ',RCFC12_per
     2565    WRITE(lunout,*)' cvl_comp_threshold=', cvl_comp_threshold
     2566    WRITE(lunout,*)' cvl_sig2feed=', cvl_sig2feed
     2567    WRITE(lunout,*)' cvl_corr=', cvl_corr
     2568    WRITE(lunout,*)'ok_lic_melt=', ok_lic_melt
     2569    WRITE(lunout,*)'ok_lic_cond=', ok_lic_cond
     2570    WRITE(lunout,*)'iflag_cycle_diurne=',iflag_cycle_diurne
     2571    WRITE(lunout,*)'soil_model=',soil_model
     2572    WRITE(lunout,*)'new_oliq=',new_oliq
     2573    WRITE(lunout,*)'ok_orodr=',ok_orodr
     2574    WRITE(lunout,*)'ok_orolf=',ok_orolf
     2575    WRITE(lunout,*)'ok_limitvrai=',ok_limitvrai
     2576    WRITE(lunout,*)'nbapp_rad=',nbapp_rad
     2577    WRITE(lunout,*)'iflag_con=',iflag_con
     2578    WRITE(lunout,*)'nbapp_cv=',nbapp_cv
     2579    WRITE(lunout,*)'nbapp_wk=',nbapp_wk
     2580    WRITE(lunout,*)'iflag_ener_conserv=',iflag_ener_conserv
     2581    WRITE(lunout,*)'ok_conserv_q=',ok_conserv_q
     2582    WRITE(lunout,*)'iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
     2583    WRITE(lunout,*)'iflag_bergeron=',iflag_bergeron
     2584    WRITE(lunout,*)' epmax = ', epmax
     2585    WRITE(lunout,*)' coef_epmax_cape = ', coef_epmax_cape
     2586    WRITE(lunout,*)' ok_adj_ema = ', ok_adj_ema
     2587    WRITE(lunout,*)' iflag_clw = ', iflag_clw
     2588    WRITE(lunout,*)' cld_lc_lsc = ', cld_lc_lsc
     2589    WRITE(lunout,*)' cld_lc_con = ', cld_lc_con
     2590    WRITE(lunout,*)' cld_tau_lsc = ', cld_tau_lsc
     2591    WRITE(lunout,*)' cld_tau_con = ', cld_tau_con
     2592    WRITE(lunout,*)' ffallv_lsc = ', ffallv_lsc
     2593    WRITE(lunout,*)' ffallv_con = ', ffallv_con
     2594    WRITE(lunout,*)' coef_eva = ', coef_eva
     2595    WRITE(lunout,*)' reevap_ice = ', reevap_ice
     2596    WRITE(lunout,*)' iflag_pdf = ', iflag_pdf
     2597    WRITE(lunout,*)' iflag_cld_th = ', iflag_cld_th
     2598    WRITE(lunout,*)' iflag_cld_cv = ', iflag_cld_cv
     2599    WRITE(lunout,*)' tau_cld_cv = ', tau_cld_cv
     2600    WRITE(lunout,*)' coefw_cld_cv = ', coefw_cld_cv
     2601    WRITE(lunout,*)' iflag_radia = ', iflag_radia
     2602    WRITE(lunout,*)' iflag_rrtm = ', iflag_rrtm
     2603    WRITE(lunout,*)' NSW = ', NSW
     2604    WRITE(lunout,*)' iflag_albedo = ', iflag_albedo !albedo SB
     2605    WRITE(lunout,*)' ok_chlorophyll =',ok_chlorophyll ! albedo SB
     2606    WRITE(lunout,*)' iflag_ratqs = ', iflag_ratqs
     2607    WRITE(lunout,*)' seuil_inversion = ', seuil_inversion
     2608    WRITE(lunout,*)' fact_cldcon = ', fact_cldcon
     2609    WRITE(lunout,*)' facttemps = ', facttemps
     2610    WRITE(lunout,*)' ok_newmicro = ',ok_newmicro
     2611    WRITE(lunout,*)' ratqsbas = ',ratqsbas
     2612    WRITE(lunout,*)' ratqshaut = ',ratqshaut
     2613    WRITE(lunout,*)' tau_ratqs = ',tau_ratqs
     2614    WRITE(lunout,*)' top_height = ',top_height
     2615    WRITE(lunout,*)' rad_froid = ',rad_froid
     2616    WRITE(lunout,*)' rad_chau1 = ',rad_chau1
     2617    WRITE(lunout,*)' rad_chau2 = ',rad_chau2
     2618    WRITE(lunout,*)' t_glace_min = ',t_glace_min
     2619    WRITE(lunout,*)' t_glace_max = ',t_glace_max
     2620    WRITE(lunout,*)' exposant_glace = ',exposant_glace
     2621    WRITE(lunout,*)' iflag_t_glace = ',iflag_t_glace
     2622    WRITE(lunout,*)' iflag_cloudth_vert = ',iflag_cloudth_vert
     2623    WRITE(lunout,*)' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
     2624    WRITE(lunout,*)' iflag_ice_thermo = ',iflag_ice_thermo
     2625    WRITE(lunout,*)' rei_min = ',rei_min
     2626    WRITE(lunout,*)' rei_max = ',rei_max
     2627    WRITE(lunout,*)' overlap = ',overlap
     2628    WRITE(lunout,*)' cdmmax = ',cdmmax
     2629    WRITE(lunout,*)' cdhmax = ',cdhmax
     2630    WRITE(lunout,*)' ksta = ',ksta
     2631    WRITE(lunout,*)' ksta_ter = ',ksta_ter
     2632    WRITE(lunout,*)' f_ri_cd_min = ',f_ri_cd_min
     2633    WRITE(lunout,*)' ok_kzmin = ',ok_kzmin
     2634    WRITE(lunout,*)' pbl_lmixmin_alpha = ',pbl_lmixmin_alpha
     2635    WRITE(lunout,*)' fmagic = ',fmagic
     2636    WRITE(lunout,*)' pmagic = ',pmagic
     2637    WRITE(lunout,*)' ok_ade = ',ok_ade
     2638    WRITE(lunout,*)' ok_volcan = ',ok_volcan
     2639    WRITE(lunout,*)' ok_aie = ',ok_aie
     2640    WRITE(lunout,*)' ok_alw = ',ok_alw
     2641    WRITE(lunout,*)' aerosol_couple = ', aerosol_couple
     2642    WRITE(lunout,*)' chemistry_couple = ', chemistry_couple
     2643    WRITE(lunout,*)' flag_aerosol = ', flag_aerosol
     2644    WRITE(lunout,*)' flag_aerosol_strat= ', flag_aerosol_strat
     2645    WRITE(lunout,*) ' flag_aer_feedback= ', flag_aer_feedback
     2646    WRITE(lunout,*)' new_aod = ', new_aod
     2647    WRITE(lunout,*)' aer_type = ',aer_type
     2648    WRITE(lunout,*)' bl95_b0 = ',bl95_b0
     2649    WRITE(lunout,*)' bl95_b1 = ',bl95_b1
     2650    WRITE(lunout,*)' lev_histhf = ',lev_histhf
     2651    WRITE(lunout,*)' lev_histday = ',lev_histday
     2652    WRITE(lunout,*)' lev_histmth = ',lev_histmth
     2653    WRITE(lunout,*)' lev_histins = ',lev_histins
     2654    WRITE(lunout,*)' lev_histLES = ',lev_histLES
     2655    WRITE(lunout,*)' lev_histdayNMC = ',lev_histdayNMC
     2656    WRITE(lunout,*)' levout_histNMC = ',levout_histNMC
     2657    WRITE(lunout,*)' ok_histNMC = ',ok_histNMC
     2658    WRITE(lunout,*)' freq_outNMC = ',freq_outNMC
     2659    WRITE(lunout,*)' freq_calNMC = ',freq_calNMC
     2660    WRITE(lunout,*)' iflag_pbl = ', iflag_pbl
    26492661!FC
    2650     write(lunout,*)' ifl_pbltree = ', ifl_pbltree
    2651     write(lunout,*)' Cd_frein = ', Cd_frein
    2652     write(lunout,*)' iflag_pbl_split = ', iflag_pbl_split
    2653     write(lunout,*)' iflag_order2_sollw = ', iflag_order2_sollw
    2654     write(lunout,*)' iflag_thermals = ', iflag_thermals
    2655     write(lunout,*)' iflag_thermals_ed = ', iflag_thermals_ed
    2656     write(lunout,*)' fact_thermals_ed_dz = ', fact_thermals_ed_dz
    2657     write(lunout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
    2658     write(lunout,*)' iflag_thermals_closure = ', iflag_thermals_closure
    2659     write(lunout,*)' iflag_clos = ', iflag_clos
    2660     write(lunout,*)' coef_clos_ls = ', coef_clos_ls
    2661     write(lunout,*)' type_run = ',type_run
    2662     write(lunout,*)' ok_cosp = ',ok_cosp
    2663     write(lunout,*)' ok_airs = ',ok_airs
    2664 
    2665     write(lunout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
    2666     write(lunout,*)' ok_journeCOSP = ',ok_journeCOSP
    2667     write(lunout,*)' ok_hfCOSP =',ok_hfCOSP
    2668     write(lunout,*)' solarlong0 = ', solarlong0
    2669     write(lunout,*)' qsol0 = ', qsol0
    2670     write(lunout,*)' evap0 = ', evap0
    2671     write(lunout,*)' albsno0 = ', albsno0
    2672     write(lunout,*)' iflag_sic = ', iflag_sic
    2673     write(lunout,*)' inertie_sol = ', inertie_sol
    2674     write(lunout,*)' inertie_sic = ', inertie_sic
    2675     write(lunout,*)' inertie_lic = ', inertie_lic
    2676     write(lunout,*)' inertie_sno = ', inertie_sno
    2677     write(lunout,*)' f_cdrag_ter = ',f_cdrag_ter
    2678     write(lunout,*)' f_cdrag_oce = ',f_cdrag_oce
    2679     write(lunout,*)' f_rugoro = ',f_rugoro
    2680     write(lunout,*)' z0min = ',z0min
    2681     write(lunout,*)' supcrit1 = ', supcrit1
    2682     write(lunout,*)' supcrit2 = ', supcrit2
    2683     write(lunout,*)' iflag_mix = ', iflag_mix
    2684     write(lunout,*)' iflag_mix_adiab = ', iflag_mix_adiab
    2685     write(lunout,*)' scut = ', scut
    2686     write(lunout,*)' qqa1 = ', qqa1
    2687     write(lunout,*)' qqa2 = ', qqa2
    2688     write(lunout,*)' gammas = ', gammas
    2689     write(lunout,*)' Fmax = ', Fmax
    2690     write(lunout,*)' tmax_fonte_cv = ', tmax_fonte_cv
    2691     write(lunout,*)' alphas = ', alphas
    2692     write(lunout,*)' iflag_wake = ', iflag_wake
    2693     write(lunout,*)' alp_offset = ', alp_offset
     2662    WRITE(lunout,*)' ifl_pbltree = ', ifl_pbltree
     2663    WRITE(lunout,*)' Cd_frein = ', Cd_frein
     2664    WRITE(lunout,*)' iflag_pbl_split = ', iflag_pbl_split
     2665    WRITE(lunout,*)' iflag_order2_sollw = ', iflag_order2_sollw
     2666    WRITE(lunout,*)' iflag_thermals = ', iflag_thermals
     2667    WRITE(lunout,*)' iflag_thermals_ed = ', iflag_thermals_ed
     2668    WRITE(lunout,*)' fact_thermals_ed_dz = ', fact_thermals_ed_dz
     2669    WRITE(lunout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
     2670    WRITE(lunout,*)' iflag_thermals_closure = ', iflag_thermals_closure
     2671    WRITE(lunout,*)' iflag_clos = ', iflag_clos
     2672    WRITE(lunout,*)' coef_clos_ls = ', coef_clos_ls
     2673    WRITE(lunout,*)' type_run = ',type_run
     2674    WRITE(lunout,*)' ok_cosp = ',ok_cosp
     2675    WRITE(lunout,*)' ok_airs = ',ok_airs
     2676
     2677    WRITE(lunout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
     2678    WRITE(lunout,*)' ok_journeCOSP = ',ok_journeCOSP
     2679    WRITE(lunout,*)' ok_hfCOSP =',ok_hfCOSP
     2680    WRITE(lunout,*)' solarlong0 = ', solarlong0
     2681    WRITE(lunout,*)' qsol0 = ', qsol0
     2682    WRITE(lunout,*)' evap0 = ', evap0
     2683    WRITE(lunout,*)' albsno0 = ', albsno0
     2684    WRITE(lunout,*)' iflag_sic = ', iflag_sic
     2685    WRITE(lunout,*)' inertie_sol = ', inertie_sol
     2686    WRITE(lunout,*)' inertie_sic = ', inertie_sic
     2687    WRITE(lunout,*)' inertie_lic = ', inertie_lic
     2688    WRITE(lunout,*)' inertie_sno = ', inertie_sno
     2689    WRITE(lunout,*)' f_cdrag_ter = ',f_cdrag_ter
     2690    WRITE(lunout,*)' f_cdrag_oce = ',f_cdrag_oce
     2691    WRITE(lunout,*)' f_rugoro = ',f_rugoro
     2692    WRITE(lunout,*)' z0min = ',z0min
     2693    WRITE(lunout,*)' supcrit1 = ', supcrit1
     2694    WRITE(lunout,*)' supcrit2 = ', supcrit2
     2695    WRITE(lunout,*)' iflag_mix = ', iflag_mix
     2696    WRITE(lunout,*)' iflag_mix_adiab = ', iflag_mix_adiab
     2697    WRITE(lunout,*)' scut = ', scut
     2698    WRITE(lunout,*)' qqa1 = ', qqa1
     2699    WRITE(lunout,*)' qqa2 = ', qqa2
     2700    WRITE(lunout,*)' gammas = ', gammas
     2701    WRITE(lunout,*)' Fmax = ', Fmax
     2702    WRITE(lunout,*)' tmax_fonte_cv = ', tmax_fonte_cv
     2703    WRITE(lunout,*)' alphas = ', alphas
     2704    WRITE(lunout,*)' iflag_wake = ', iflag_wake
     2705    WRITE(lunout,*)' alp_offset = ', alp_offset
    26942706    ! nrlmd le 10/04/2012
    2695     write(lunout,*)' iflag_trig_bl = ', iflag_trig_bl
    2696     write(lunout,*)' s_trig = ', s_trig
    2697     write(lunout,*)' tau_trig_shallow = ', tau_trig_shallow
    2698     write(lunout,*)' tau_trig_deep = ', tau_trig_deep
    2699     write(lunout,*)' iflag_clos_bl = ', iflag_clos_bl
     2707    WRITE(lunout,*) ' iflag_trig_bl = ', iflag_trig_bl
     2708    WRITE(lunout,*) ' s_trig = ', s_trig
     2709    WRITE(lunout,*) ' tau_trig_shallow = ', tau_trig_shallow
     2710    WRITE(lunout,*) ' tau_trig_deep = ', tau_trig_deep
     2711    WRITE(lunout,*) ' iflag_clos_bl = ', iflag_clos_bl
    27002712    ! fin nrlmd le 10/04/2012
    27012713
    2702     write(lunout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
     2714    WRITE(lunout,*) ' lonmin lonmax latmin latmax bilKP_ins =',&
    27032715         lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    2704     write(lunout,*)' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
     2716    WRITE(lunout,*) ' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
    27052717         ecrit_hf, ecrit_ins, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES
    27062718
    2707     write(lunout,*) 'ok_strato = ', ok_strato
    2708     write(lunout,*) 'ok_hines = ',  ok_hines
    2709     write(lunout,*) 'ok_gwd_rando = ',  ok_gwd_rando
    2710     write(lunout,*) 'ok_qch4 = ',  ok_qch4
    2711     write(lunout,*) 'gwd_rando_ruwmax = ', gwd_rando_ruwmax
    2712     write(lunout,*) 'gwd_rando_sat = ', gwd_rando_sat
    2713     write(lunout,*) 'gwd_front_ruwmax = ', gwd_front_ruwmax
    2714     write(lunout,*) 'gwd_front_sat = ', gwd_front_sat
    2715     write(lunout,*) 'SSO gkdrag =',gkdrag
    2716     write(lunout,*) 'SSO grahilo=',grahilo
    2717     write(lunout,*) 'SSO grcrit=',grcrit
    2718     write(lunout,*) 'SSO gfrcrit=',gfrcrit
    2719     write(lunout,*) 'SSO gkwake=',gkwake
    2720     write(lunout,*) 'SSO gklift=',gklift
    2721     write(lunout,*) 'adjust_tropopause = ', adjust_tropopause
    2722     write(lunout,*) 'ok_daily_climoz = ',ok_daily_climoz
    2723     write(lunout,*) 'read_climoz = ', read_climoz
    2724     write(lunout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
    2725     write(lunout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
     2719    WRITE(lunout,*) ' ok_strato = ', ok_strato
     2720    WRITE(lunout,*) ' ok_hines = ',  ok_hines
     2721    WRITE(lunout,*) ' ok_gwd_rando = ',  ok_gwd_rando
     2722    WRITE(lunout,*) ' ok_qch4 = ',  ok_qch4
     2723    WRITE(lunout,*) ' gwd_rando_ruwmax = ', gwd_rando_ruwmax
     2724    WRITE(lunout,*) ' gwd_rando_sat = ', gwd_rando_sat
     2725    WRITE(lunout,*) ' gwd_front_ruwmax = ', gwd_front_ruwmax
     2726    WRITE(lunout,*) ' gwd_front_sat = ', gwd_front_sat
     2727    WRITE(lunout,*) ' SSO gkdrag =',gkdrag
     2728    WRITE(lunout,*) ' SSO grahilo=',grahilo
     2729    WRITE(lunout,*) ' SSO grcrit=',grcrit
     2730    WRITE(lunout,*) ' SSO gfrcrit=',gfrcrit
     2731    WRITE(lunout,*) ' SSO gkwake=',gkwake
     2732    WRITE(lunout,*) ' SSO gklift=',gklift
     2733    WRITE(lunout,*) ' adjust_tropopause = ', adjust_tropopause
     2734    WRITE(lunout,*) ' ok_daily_climoz = ',ok_daily_climoz
     2735    WRITE(lunout,*) ' read_climoz = ', read_climoz
     2736    WRITE(lunout,*) ' carbon_cycle_tr = ', carbon_cycle_tr
     2737    WRITE(lunout,*) ' carbon_cycle_cpl = ', carbon_cycle_cpl
    27262738
    27272739    !$OMP END MASTER
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/physiq_mod.F90

    r3521 r3525  
    10671067    INTEGER, SAVE :: flag_aerosol_strat
    10681068    !$OMP THREADPRIVATE(flag_aerosol_strat)
     1069    !
     1070    !--INTERACTIVE AEROSOL FEEDBACK ON RADIATION
     1071    LOGICAL, SAVE :: flag_aer_feedback
     1072    !$OMP THREADPRIVATE(flag_aer_feedback)
     1073
    10691074    !c-fin STRAT AEROSOL
    10701075    !
     
    12341239            iflag_cld_th,iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    12351240            ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, aerosol_couple, &
    1236             chemistry_couple, flag_aerosol, flag_aerosol_strat, new_aod, &
     1241            chemistry_couple, flag_aerosol, flag_aerosol_strat,         &
     1242            flag_aer_feedback, new_aod, &
    12371243            flag_bc_internal_mixture, bl95_b0, bl95_b1, &
    12381244                                ! nv flags pour la convection et les
     
    39083914               cldfrarad, cldemirad, cldtaurad, &
    39093915               ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie, ok_volcan, &
    3910                flag_aerosol, flag_aerosol_strat, &
     3916               flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    39113917               tau_aero, piz_aero, cg_aero, &
    39123918               tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, &
     
    39944000                     cldfrarad, cldemirad, cldtaurad, &
    39954001                     ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie, ok_volcan, &
    3996                      flag_aerosol, flag_aerosol_strat, &
     4002                     flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    39974003                     tau_aero, piz_aero, cg_aero, &
    39984004                     tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, &
     
    48734879      dryaod_diag=.FALSE.
    48744880      ok_4xCO2atm= .FALSE.
     4881!      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    48754882
    48764883      IF (is_master) then
     
    49114918      call bcast(dryaod_diag)
    49124919      call bcast(ok_4xCO2atm)
     4920!      write (lunout,*)'ok_4xCO2atm= ',swaero_diag, swaerofree_diag, dryaod_diag, ok_4xCO2atm
    49134921#endif
    49144922    endif
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/radlwsw_m.F90

    r3426 r3525  
    1717   cldfra, cldemi, cldtaupd,&
    1818   ok_ade, ok_aie, ok_volcan, flag_aerosol,&
    19    flag_aerosol_strat,&
     19   flag_aerosol_strat, flag_aer_feedback, &
    2020   tau_aero, piz_aero, cg_aero,&
    2121   tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,& ! rajoute par OB pour RRTM
     
    104104  ! flag_aerosol-input-I- aerosol flag from 0 to 6
    105105  ! flag_aerosol_strat-input-I- use stratospheric aerosols flag (0, 1, 2)
     106  ! flag_aer_feedback-input-I- activate aerosol radiative feedback (T, F)
    106107  ! tau_ae, piz_ae, cg_ae-input-R- aerosol optical properties (calculated in aeropt.F)
    107108  ! cldtaupi-input-R- epaisseur optique des nuages dans le visible
     
    201202  INTEGER, INTENT(in)  :: flag_aerosol                                   ! takes value 0 (no aerosol) or 1 to 6 (aerosols)
    202203  INTEGER, INTENT(in)  :: flag_aerosol_strat                             ! use stratospheric aerosols
     204  LOGICAL, INTENT(in)  :: flag_aer_feedback                              ! activate aerosol radiative feedback
    203205  REAL,    INTENT(in)  :: cldfra(KLON,KLEV), cldemi(KLON,KLEV), cldtaupd(KLON,KLEV)
    204206  REAL,    INTENT(in)  :: tau_aero(KLON,KLEV,naero_grp,2)                        ! aerosol optical properties (see aeropt.F)
     
    873875         ZTOPLWAIAERO,ZSOLLWAIAERO, &
    874876         ZLWADAERO, & !--NL
    875          ok_ade, ok_aie, ok_volcan, flag_aerosol,flag_aerosol_strat) ! flags aerosols
     877         ok_ade, ok_aie, ok_volcan, flag_aerosol,flag_aerosol_strat, &
     878         flag_aer_feedback) ! flags aerosols
    876879           
    877880!        print *,'RADLWSW: apres RECMWF'
  • LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/rrtm/recmwf_aero.F90

    r3408 r3525  
    3737 & PLWADAERO,& !--NL
    3838!..end
    39  & ok_ade, ok_aie, ok_volcan, flag_aerosol,flag_aerosol_strat)
     39 & ok_ade, ok_aie, ok_volcan, flag_aerosol,flag_aerosol_strat,flag_aer_feedback)
    4040!--fin
    4141
     
    8787! flag_aerosol-input-I- aerosol flag from 0 to 7
    8888! flag_aerosol_strat-input-I- use stratospheric aerosols flag (T/F)
     89! flag_aer_feedback-input-I- use aerosols radiative effect flag (T/F)
    8990! PPIZA_NAT  : (KPROMA,KLEV,NSW); Single scattering albedo of natural aerosol
    9091! PCGA_NAT   : (KPROMA,KLEV,NSW); Assymetry factor for natural aerosol
     
    218219INTEGER, INTENT(in)  :: flag_aerosol           ! takes value 0 (no aerosol) or 1 to 6 (aerosols)
    219220LOGICAL, INTENT(in)  :: flag_aerosol_strat     ! use stratospheric aerosols
    220 REAL(KIND=JPRB)   ,INTENT(OUT)   :: PTOPSWADAERO(KPROMA), PSOLSWADAERO(KPROMA)       ! Aerosol direct forcing at TOA and surface
     221LOGICAL, INTENT(in)  :: flag_aer_feedback      ! use aerosols radiative feedback
     222REAL(KIND=JPRB)   ,INTENT(out)   :: PTOPSWADAERO(KPROMA), PSOLSWADAERO(KPROMA)       ! Aerosol direct forcing at TOA and surface
    221223REAL(KIND=JPRB)   ,INTENT(OUT)   :: PTOPSWAD0AERO(KPROMA), PSOLSWAD0AERO(KPROMA)     ! Aerosol direct forcing at TOA and surface
    222224REAL(KIND=JPRB)   ,INTENT(OUT)   :: PTOPSWAIAERO(KPROMA), PSOLSWAIAERO(KPROMA)       ! ditto, indirect
     
    305307! FALSE: fluxes use no aerosols (case 1)
    306308! to be used only for maintaining bit reproducibility with aerosol diagnostics activated
    307 LOGICAL :: AEROSOLFEEDBACK_ACTIVE = .TRUE.
     309 LOGICAL :: AEROSOLFEEDBACK_ACTIVE ! now externalized from .def files
    308310
    309311!OB - Fluxes including aerosol effects
     
    342344IBEG=KST
    343345IEND=KEND
     346
     347AEROSOLFEEDBACK_ACTIVE = flag_aer_feedback !NL: externalize aer feedback
     348
    344349
    345350!*       1.    PREPARATORY WORK
Note: See TracChangeset for help on using the changeset viewer.