Ignore:
Timestamp:
Jul 22, 2024, 6:53:44 PM (7 months ago)
Author:
abarral
Message:

Remove CRAY key (obsolete calls to functions that don't exist anymore, bugs in some implementations, irrelevant now)
Replace usage of CPP_XIOS key by using_xios logical
Remove always unused testcpu bits
Replace most uses of CPP_StratAer by the corresponding logical defined in lmdz_cppkeys_wrapper.F90 [this breaks iso compilation because phyiso doesn't define all aerosols - to be fixed later]
Replaces uses of include "yomcst.h" by the lmdz_yomcst.f90 module in .[fF]90 files

Location:
LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer
Files:
16 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/aer_sedimnt.F90

    r5087 r5098  
    2222  USE infotrac_phy
    2323  USE aerophys
    24   USE YOMCST
     24  USE lmdz_yomcst
    2525
    2626IMPLICIT NONE
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/calcaerosolstrato_rrtm.F90

    r5082 r5098  
    99  USE dimphy
    1010  USE temps_mod
    11   USE YOMCST
     11  USE lmdz_yomcst
    1212
    1313  IMPLICIT NONE
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/coagulate.F90

    r5087 r5098  
    2828  USE phys_local_var_mod, ONLY: DENSO4, DENSO4B, f_r_wet, f_r_wetB
    2929  USE strataer_local_var_mod, ONLY: flag_new_strat_compo
     30  USE lmdz_yomcst
    3031 
    3132  IMPLICIT NONE
     
    8384  REAL                                          :: EvdW
    8485
    85   include "YOMCST.h"
    86 
    8786! ff(i,j,k): Volume fraction of Vi,j that is partitioned to each model bin k
    8887! just need to be calculated in model initialization because mdw(:) size is fixed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/cond_evap_tstep_mod.F90

    r5087 r5098  
    2828      USE aerophys
    2929      USE infotrac_phy
    30       USE YOMCST, ONLY : RPI
     30      USE lmdz_yomcst, ONLY : RPI
    3131      USE sulfate_aer_mod, ONLY : wph2so4, surftension, solh2so4, rpmvh2so4
    3232      USE strataer_local_var_mod, ONLY : ALPH2SO4, RRSI
    3333     
    3434      IMPLICIT NONE
    35      
     35
    3636      REAL, PARAMETER :: third=1./3.
    3737     
     
    177177      USE aerophys
    178178      USE infotrac_phy
    179       USE YOMCST, ONLY : RPI
     179      USE lmdz_yomcst, ONLY : RPI
    180180      USE strataer_local_var_mod, ONLY : ALPH2SO4, RRSI
    181181
     
    290290      USE aerophys
    291291      USE infotrac_phy
    292       USE YOMCST, ONLY : RPI
     292      USE lmdz_yomcst, ONLY : RPI
    293293      USE strataer_local_var_mod, ONLY : RRSI,Vbin
    294294     
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/interp_sulf_input.F90

    r5088 r5098  
    1818  USE infotrac_phy
    1919  USE aerophys
    20   USE YOMCST
     20  USE lmdz_yomcst
    2121  USE strataer_local_var_mod, ONLY : flag_newclim_file,flag_verbose_strataer
    2222
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/micphy_tstep.F90

    r5087 r5098  
    1313  USE cond_evap_tstep_mod
    1414  USE sulfate_aer_mod, ONLY : STRAACT
    15   USE YOMCST, ONLY : RPI, RD, RG
     15  USE lmdz_yomcst, ONLY : RPI, RD, RG
    1616  USE print_control_mod, ONLY: lunout
    1717  USE strataer_local_var_mod ! contains also RRSI and Vbin
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/miecalc_aer.F90

    r5087 r5098  
    2020  USE infotrac_phy, ONLY : nbtr, nbtr_bin, nbtr_sulgas, id_SO2_strat
    2121  USE dimphy
    22   USE YOMCST  , ONLY : RG, RPI
     22  USE lmdz_yomcst  , ONLY : RG, RPI
    2323  USE mod_phys_lmdz_para, only: gather, scatter, bcast
    2424  USE mod_grid_phy_lmdz, ONLY : klon_glo
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/nucleation_tstep_mod.F90

    r5087 r5098  
    1111  USE infotrac_phy
    1212  USE strataer_local_var_mod, ONLY : flag_new_nucl
     13  USE lmdz_yomcst
    1314 
    1415  IMPLICIT NONE
     
    3738  REAL airn    ! Air molecule concentration in (cm-3) NOT IN USE
    3839  REAL ipr     ! Ion pair production rate (cm-3 s-1) NOT IN USE
    39 
    40   include "YOMCST.h"
    4140
    4241  ! call nucleation routine
     
    332331
    333332  USE aerophys
     333  USE lmdz_yomcst
    334334
    335335  IMPLICIT NONE
     
    385385  DOUBLE PRECISION :: xloss       ! Ion loss rate
    386386  DOUBLE PRECISION :: recomb      ! Ion-ion recombination rate
    387 
    388   include "YOMCST.h"
    389387
    390388  !--- 0) Initializations:
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/ocs_to_so2.F90

    r5082 r5098  
    77  USE aerophys
    88  USE infotrac_phy
    9   USE YOMCST, ONLY : RG
     9  USE lmdz_yomcst, ONLY : RG
    1010  USE phys_local_var_mod, ONLY : OCS_lifetime, budg_3D_ocs_to_so2, budg_ocs_to_so2
    1111  USE strataer_local_var_mod, ONLY : flag_min_rreduce
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/so2_to_h2so4.F90

    r5087 r5098  
    77  USE aerophys
    88  USE infotrac_phy
    9   USE YOMCST, ONLY : RG, RD
     9  USE lmdz_yomcst, ONLY : RG, RD
    1010  ! lifetime (sec) et O3_clim (VMR)
    1111  USE phys_local_var_mod, ONLY : SO2_lifetime, H2SO4_lifetime, O3_clim, budg_3D_so2_to_h2so4, budg_so2_to_h2so4
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/stratH2O_methox.F90

    r5088 r5098  
    1919  USE infotrac_phy
    2020  USE aerophys
    21   USE YOMCST
     21  USE lmdz_yomcst
    2222  USE strataer_local_var_mod, ONLY : flag_newclim_file
    2323 
    2424  IMPLICIT NONE
    25  
     25
    2626  include "dimensions.h"
    2727 
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/strataer_emiss_mod.F90

    r5082 r5098  
    219219    USE print_control_mod, ONLY : lunout
    220220    USE strataer_local_var_mod
    221 
    222     INCLUDE "YOMCST.h"  !--RPI
     221    USE lmdz_yomcst, ONLY: RPI
    223222
    224223    ! local var
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/strataer_local_var_mod.F90

    r5082 r5098  
    11MODULE strataer_local_var_mod
    2 ! This module contains strato microphysic model parameters & variables
    3  
     2  ! This module contains strato microphysic model parameters & variables
     3
    44  IMPLICIT NONE
    5  
     5
    66  !============= GENERAL PARAMS =============
    77  !flag for type emission scenario: (0) background aer ; (1) volcanic eruption with Sulfur ;
    88  !(2,3) strato aer injections (SAI) ; (4) volcanic eruption chimistry; (5) rocket
    9   INTEGER,SAVE :: flag_emit
     9  INTEGER, SAVE :: flag_emit
    1010  !$OMP THREADPRIVATE(flag_emit)
    11  
     11
    1212  ! flag for emission altitude distribution: (0) gaussian; (1) uniform
    13   INTEGER,SAVE :: flag_emit_distrib
     13  INTEGER, SAVE :: flag_emit_distrib
    1414  !$OMP THREADPRIVATE(flag_emit_distrib)
    15  
     15
    1616  ! flag to choose nucleation nucleation method
    17   LOGICAL,SAVE :: flag_new_nucl   ! T=new routine from A. Maattanen (LATMOS), F=older routine from H. Vehkamäki (FMI)
     17  LOGICAL, SAVE :: flag_new_nucl   ! T=new routine from A. Maattanen (LATMOS), F=older routine from H. Vehkamäki (FMI)
    1818  !$OMP THREADPRIVATE(flag_new_nucl)
    19  
     19
    2020  ! Use relative humidity from 2D model stratospheric H2O because LMDz is too dry in the stratosphere
    2121  ! (no CH4 oxidation)
    22   LOGICAL,SAVE :: flag_H2O2d_nucleation
     22  LOGICAL, SAVE :: flag_H2O2d_nucleation
    2323  !$OMP THREADPRIVATE(flag_H2O2d_nucleation)
    24  
     24
    2525  ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction
    2626  ! with O3 (Bekki, 1995). As a result, SO2 lifetime is extended. 2D model O3 climatologies are needed.
    27   LOGICAL,SAVE :: flag_OH_reduced
     27  LOGICAL, SAVE :: flag_OH_reduced
    2828  !$OMP THREADPRIVATE(flag_OH_reduced)
    29  
     29
    3030  ! H2SO4 photolysis: H2SO4 is converted into SO2 by complex photolytic processes. Here simplified approach
    3131  ! by setting H2SO4 cross-sections = 0.3*HCl cross-sections (Rinsland et al., 1995)
    32   LOGICAL,SAVE :: flag_H2SO4_photolysis
     32  LOGICAL, SAVE :: flag_H2SO4_photolysis
    3333  !$OMP THREADPRIVATE(flag_H2SO4_photolysis)
    34  
     34
    3535  ! flag for minimum lifetime (=1.5 pdt phys)
    36   LOGICAL,SAVE :: flag_min_rreduce
     36  LOGICAL, SAVE :: flag_min_rreduce
    3737  !$OMP THREADPRIVATE(flag_min_rreduce)
    38  
     38
    3939  ! flag to read new climato (O3, H2O & H2SO4_LIFET)
    40   LOGICAL,SAVE :: flag_newclim_file
     40  LOGICAL, SAVE :: flag_newclim_file
    4141  !$OMP THREADPRIVATE(flag_newclim_file)
    42  
     42
    4343  ! flag to choose new H2SO4 density and weight percent from Tabazadeh et al. (1994).
    44   LOGICAL,SAVE :: flag_new_strat_compo
     44  LOGICAL, SAVE :: flag_new_strat_compo
    4545  !$OMP THREADPRIVATE(flag_new_strat_compo)
    46  
     46
    4747  ! Verbose mode to get more print info
    4848  LOGICAL, SAVE :: flag_verbose_strataer
    4949  !$OMP THREADPRIVATE(flag_verbose_strataer)
    50  
    51  
     50
     51
    5252  !============= NUCLEATION VARS =============
    5353  ! MOLECULAR ACCOMODATION OF H2SO4 (Raes and Van Dingen)
    54   REAL,SAVE    :: ALPH2SO4               ! H2SO4 accommodation  coefficient [condensation/evaporation]
     54  REAL, SAVE :: ALPH2SO4               ! H2SO4 accommodation  coefficient [condensation/evaporation]
    5555  !$OMP THREADPRIVATE(ALPH2SO4)
    56  
     56
    5757  ! flag to constraint nucleation rate in a lat/pres box
    58   LOGICAL,SAVE :: flag_nuc_rate_box      ! Nucleation rate limit or not to a lat/pres
     58  LOGICAL, SAVE :: flag_nuc_rate_box      ! Nucleation rate limit or not to a lat/pres
    5959  !$OMP THREADPRIVATE(flag_nuc_rate_box)
    60   REAL,SAVE    :: nuclat_min             ! min lat to activate nuc rate
    61   REAL,SAVE    :: nuclat_max             ! max lat to activate nuc rate
    62   REAL,SAVE    :: nucpres_min            ! min pres to activate nuc rate
    63   REAL,SAVE    :: nucpres_max            ! max pres to activate nuc rate
     60  REAL, SAVE :: nuclat_min             ! min lat to activate nuc rate
     61  REAL, SAVE :: nuclat_max             ! max lat to activate nuc rate
     62  REAL, SAVE :: nucpres_min            ! min pres to activate nuc rate
     63  REAL, SAVE :: nucpres_max            ! max pres to activate nuc rate
    6464  !$OMP THREADPRIVATE(nuclat_min, nuclat_max, nucpres_min, nucpres_max)
    6565
    66   LOGICAL,SAVE :: ok_qemiss
     66  LOGICAL, SAVE :: ok_qemiss
    6767  !$OMP THREADPRIVATE(ok_qemiss)
    68   INTEGER,SAVE :: flh2o  ! ds stratemit : flh2o =0 (tr_seri), flh2o=1 (dq)
     68  INTEGER, SAVE :: flh2o  ! ds stratemit : flh2o =0 (tr_seri), flh2o=1 (dq)
    6969  !$OMP THREADPRIVATE(flh2o)
    70  
    71   REAL,ALLOCATABLE,SAVE    :: budg_emi(:,:)            !DIMENSION(klon,n)
     70
     71  REAL, ALLOCATABLE, SAVE :: budg_emi(:, :)            !DIMENSION(klon,n)
    7272  !$OMP THREADPRIVATE(budg_emi)
    73  
    74  
     73
     74
    7575  !============= EMISSION VARS =============
    7676  !--flag_emit=1 OR == 4 -- Volcanic eruption(s)
    77   INTEGER,SAVE            :: nErupt                    ! number of eruptions specs
    78   REAL,SAVE                :: injdur                    ! volcanic injection duration
     77  INTEGER, SAVE :: nErupt                    ! number of eruptions specs
     78  REAL, SAVE :: injdur                    ! volcanic injection duration
    7979  !$OMP THREADPRIVATE(nErupt, injdur)
    80   INTEGER,ALLOCATABLE,SAVE :: year_emit_vol(:)          ! year of emission date
    81   INTEGER,ALLOCATABLE,SAVE :: mth_emit_vol(:)           ! month of emission date
    82   INTEGER,ALLOCATABLE,SAVE :: day_emit_vol(:)           ! day of emission date
     80  INTEGER, ALLOCATABLE, SAVE :: year_emit_vol(:)          ! year of emission date
     81  INTEGER, ALLOCATABLE, SAVE :: mth_emit_vol(:)           ! month of emission date
     82  INTEGER, ALLOCATABLE, SAVE :: day_emit_vol(:)           ! day of emission date
    8383  !$OMP THREADPRIVATE(year_emit_vol, mth_emit_vol, day_emit_vol)
    84   REAL,ALLOCATABLE,SAVE    :: altemiss_vol(:)           ! emission altitude in m
    85   REAL,ALLOCATABLE,SAVE    :: sigma_alt_vol(:)          ! standard deviation of emission altitude in m
     84  REAL, ALLOCATABLE, SAVE :: altemiss_vol(:)           ! emission altitude in m
     85  REAL, ALLOCATABLE, SAVE :: sigma_alt_vol(:)          ! standard deviation of emission altitude in m
    8686  !$OMP THREADPRIVATE(altemiss_vol, sigma_alt_vol)
    87   INTEGER,ALLOCATABLE,SAVE :: ponde_lonlat_vol(:)       ! lon/lat ponderation factor
    88   REAL,ALLOCATABLE,SAVE    :: xlat_min_vol(:)           ! min latitude of volcano in degree
    89   REAL,ALLOCATABLE,SAVE    :: xlat_max_vol(:)           ! max latitude of volcano in degree
    90   REAL,ALLOCATABLE,SAVE    :: xlon_min_vol(:)           ! min longitude of volcano in degree
    91   REAL,ALLOCATABLE,SAVE    :: xlon_max_vol(:)           ! max longitude of volcano in degree
     87  INTEGER, ALLOCATABLE, SAVE :: ponde_lonlat_vol(:)       ! lon/lat ponderation factor
     88  REAL, ALLOCATABLE, SAVE :: xlat_min_vol(:)           ! min latitude of volcano in degree
     89  REAL, ALLOCATABLE, SAVE :: xlat_max_vol(:)           ! max latitude of volcano in degree
     90  REAL, ALLOCATABLE, SAVE :: xlon_min_vol(:)           ! min longitude of volcano in degree
     91  REAL, ALLOCATABLE, SAVE :: xlon_max_vol(:)           ! max longitude of volcano in degree
    9292  !$OMP THREADPRIVATE(ponde_lonlat_vol, xlat_min_vol, xlat_max_vol, xlon_min_vol, xlon_max_vol)
    93  
     93
    9494  !--flag_emit=1
    95   INTEGER,SAVE             :: nAerErupt                 ! number Aerosol
     95  INTEGER, SAVE :: nAerErupt                 ! number Aerosol
    9696  !$OMP THREADPRIVATE(nAerErupt)
    97   REAL,ALLOCATABLE,SAVE    :: m_sulf_emiss_vol(:)        ! emitted sulfur mass in kgS, e.g. 7Tg(S)=14Tg(SO2)
    98   REAL,ALLOCATABLE,SAVE    :: m_aer_emiss_vol(:,:)
     97  REAL, ALLOCATABLE, SAVE :: m_sulf_emiss_vol(:)        ! emitted sulfur mass in kgS, e.g. 7Tg(S)=14Tg(SO2)
     98  REAL, ALLOCATABLE, SAVE :: m_aer_emiss_vol(:, :)
    9999  !$OMP THREADPRIVATE(m_sulf_emiss_vol,m_aer_emiss_vol)
    100  
     100
    101101  !--flag_emit=2 --SAI
    102   REAL,SAVE    :: m_aer_emiss_sai        ! emitted sulfur mass in kgS, eg 1e9=1TgS, 1e10=10TgS
    103   REAL,SAVE    :: altemiss_sai           ! emission altitude in m
    104   REAL,SAVE    :: sigma_alt_sai          ! standard deviation of emission altitude in m
     102  REAL, SAVE :: m_aer_emiss_sai        ! emitted sulfur mass in kgS, eg 1e9=1TgS, 1e10=10TgS
     103  REAL, SAVE :: altemiss_sai           ! emission altitude in m
     104  REAL, SAVE :: sigma_alt_sai          ! standard deviation of emission altitude in m
    105105  !$OMP THREADPRIVATE(m_aer_emiss_sai, altemiss_sai, sigma_alt_sai)
    106   INTEGER,SAVE    :: year_emit_sai_start
    107   INTEGER,SAVE    :: year_emit_sai_end
    108   INTEGER,SAVE    :: mth_emit_sai_start
    109   INTEGER,SAVE    :: mth_emit_sai_end
    110   INTEGER,SAVE    :: day_emit_sai_start
    111   INTEGER,SAVE    :: day_emit_sai_end
     106  INTEGER, SAVE :: year_emit_sai_start
     107  INTEGER, SAVE :: year_emit_sai_end
     108  INTEGER, SAVE :: mth_emit_sai_start
     109  INTEGER, SAVE :: mth_emit_sai_end
     110  INTEGER, SAVE :: day_emit_sai_start
     111  INTEGER, SAVE :: day_emit_sai_end
    112112  !$OMP THREADPRIVATE(year_emit_sai_start, year_emit_sai_end)
    113113  !$OMP THREADPRIVATE(mth_emit_sai_start, mth_emit_sai_end)
    114114  !$OMP THREADPRIVATE(day_emit_sai_start, day_emit_sai_end)
    115   REAL,SAVE    :: xlat_sai               ! latitude of SAI in degree
    116   REAL,SAVE    :: xlon_sai               ! longitude of SAI in degree
     115  REAL, SAVE :: xlat_sai               ! latitude of SAI in degree
     116  REAL, SAVE :: xlon_sai               ! longitude of SAI in degree
    117117  !$OMP THREADPRIVATE(xlat_sai, xlon_sai)
    118  
     118
    119119  !--flag_emit=3 -- SAI
    120   REAL,SAVE    :: xlat_max_sai           ! maximum latitude of SAI in degrees
    121   REAL,SAVE    :: xlat_min_sai           ! minimum latitude of SAI in degrees
     120  REAL, SAVE :: xlat_max_sai           ! maximum latitude of SAI in degrees
     121  REAL, SAVE :: xlat_min_sai           ! minimum latitude of SAI in degrees
    122122  !$OMP THREADPRIVATE(xlat_min_sai,xlat_max_sai)
    123  
     123
    124124  !--flag_emit=4 -- volc species
    125   INTEGER,SAVE            :: nSpeciesErupt            ! number of species Repr
    126   INTEGER,ALLOCATABLE,SAVE :: id_species(:)            ! indice species Repr
    127   REAL,ALLOCATABLE,SAVE    :: m_species_emiss_vol(:,:) ! emitted species
     125  INTEGER, SAVE :: nSpeciesErupt            ! number of species Repr
     126  INTEGER, ALLOCATABLE, SAVE :: id_species(:)            ! indice species Repr
     127  REAL, ALLOCATABLE, SAVE :: m_species_emiss_vol(:, :) ! emitted species
    128128  !$OMP THREADPRIVATE(nSpeciesErupt,id_species,m_species_emiss_vol)
    129   INTEGER,ALLOCATABLE,SAVE :: id_HCl
    130   INTEGER,ALLOCATABLE,SAVE :: id_HBr
    131   INTEGER,ALLOCATABLE,SAVE :: id_NOx
    132   INTEGER,ALLOCATABLE,SAVE :: id_H2O
     129  INTEGER, ALLOCATABLE, SAVE :: id_HCl
     130  INTEGER, ALLOCATABLE, SAVE :: id_HBr
     131  INTEGER, ALLOCATABLE, SAVE :: id_NOx
     132  INTEGER, ALLOCATABLE, SAVE :: id_H2O
    133133  !$OMP THREADPRIVATE(id_HCl,id_HBr,id_NOx,id_H2O)
    134   REAL,ALLOCATABLE,SAVE    :: m_Chlore_emiss_vol(:)   ! emitted Chlore mass
    135   REAL,ALLOCATABLE,SAVE    :: m_Brome_emiss_vol(:)    ! emitted Brome mass
    136   REAL,ALLOCATABLE,SAVE    :: m_NOx_emiss_vol(:)      ! emitted NOx mass
    137   REAL,ALLOCATABLE,SAVE    :: m_H2O_emiss_vol(:)      ! emitted H2O mass
    138   REAL,ALLOCATABLE,SAVE    :: m_H2O_emiss_vol_daily(:)
     134  REAL, ALLOCATABLE, SAVE :: m_Chlore_emiss_vol(:)   ! emitted Chlore mass
     135  REAL, ALLOCATABLE, SAVE :: m_Brome_emiss_vol(:)    ! emitted Brome mass
     136  REAL, ALLOCATABLE, SAVE :: m_NOx_emiss_vol(:)      ! emitted NOx mass
     137  REAL, ALLOCATABLE, SAVE :: m_H2O_emiss_vol(:)      ! emitted H2O mass
     138  REAL, ALLOCATABLE, SAVE :: m_H2O_emiss_vol_daily(:)
    139139  !$OMP THREADPRIVATE(m_Chlore_emiss_vol,m_Brome_emiss_vol,m_NOx_emiss_vol,m_H2O_emiss_vol)
    140140  !$OMP THREADPRIVATE(m_H2O_emiss_vol_daily)
    141  
     141
    142142  !--flag_emit=5 -- Rockets Emitted
    143   INTEGER, SAVE            :: ifreqroc        ! frequence (=2 ex: tous les 2 mois)
     143  INTEGER, SAVE :: ifreqroc        ! frequence (=2 ex: tous les 2 mois)
    144144  !$OMP THREADPRIVATE(ifreqroc)
    145   INTEGER,ALLOCATABLE,SAVE :: day_emit_roc(:) ! day of emission date
     145  INTEGER, ALLOCATABLE, SAVE :: day_emit_roc(:) ! day of emission date
    146146  !$OMP THREADPRIVATE(day_emit_roc)
    147  
    148   REAL,ALLOCATABLE,SAVE    :: RRSI(:) ! radius [cm] for each aerosol size
    149   REAL,ALLOCATABLE,SAVE    :: Vbin(:) ! volume [m3] for each aerosol size 
     147
     148  REAL, ALLOCATABLE, SAVE :: RRSI(:) ! radius [cm] for each aerosol size
     149  REAL, ALLOCATABLE, SAVE :: Vbin(:) ! volume [m3] for each aerosol size
    150150  !$OMP THREADPRIVATE(RRSI, Vbin)
    151   REAL,SAVE    :: dlat, dlon             ! delta latitude and d longitude of grid in degree
     151  REAL, SAVE :: dlat, dlon             ! delta latitude and d longitude of grid in degree
    152152  !$OMP THREADPRIVATE(dlat, dlon)
    153  
     153
    154154CONTAINS
    155    
     155
    156156  SUBROUTINE strataer_init()
    157     USE ioipsl_getin_p_mod, ONLY : getin_p
    158     USE print_control_mod, ONLY : lunout
    159     USE mod_phys_lmdz_para, ONLY : is_master
    160     USE infotrac_phy, ONLY: id_OCS_strat,id_SO2_strat,id_H2SO4_strat,nbtr_sulgas,nbtr_bin
    161     USE phys_local_var_mod, ONLY : mdw
     157    USE ioipsl_getin_p_mod, ONLY: getin_p
     158    USE print_control_mod, ONLY: lunout
     159    USE mod_phys_lmdz_para, ONLY: is_master
     160    USE infotrac_phy, ONLY: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, nbtr_sulgas, nbtr_bin
     161    USE phys_local_var_mod, ONLY: mdw
    162162    USE aerophys, ONLY: mdwmin, V_rat
    163     USE YOMCST  , ONLY : RPI
    164    
     163    USE lmdz_yomcst, ONLY: RPI
     164
    165165    INTEGER :: it
    166    
    167     WRITE(lunout,*) 'IN STRATAER_LOCAL_VAR INIT WELCOME!'
    168    
     166
     167    WRITE(lunout, *) 'IN STRATAER_LOCAL_VAR INIT WELCOME!'
     168
    169169    !============= Check Sulfur aerosols ID =============
    170     WRITE(lunout,*) 'STRATAER_LOCAL_VAR INIT: id_OCS_strat=',id_OCS_strat,' id_SO2_strat=',id_SO2_strat,' id_H2SO4_strat=',id_H2SO4_strat
    171    
     170    WRITE(lunout, *) 'STRATAER_LOCAL_VAR INIT: id_OCS_strat=', id_OCS_strat, ' id_SO2_strat=', id_SO2_strat, ' id_H2SO4_strat=', id_H2SO4_strat
     171
    172172    IF(id_OCS_strat < 0 .OR. id_OCS_strat > nbtr_sulgas) THEN
    173        WRITE(lunout,*) 'ERROR : OCS index id_OCS_strat=',id_OCS_strat,' is negative or superior than the total sulfur gases !'
    174        CALL abort_physic('strataer_local_var_mod','Wrong OCS index, check your tracer.def file.',1)
     173      WRITE(lunout, *) 'ERROR : OCS index id_OCS_strat=', id_OCS_strat, ' is negative or superior than the total sulfur gases !'
     174      CALL abort_physic('strataer_local_var_mod', 'Wrong OCS index, check your tracer.def file.', 1)
    175175    ELSEIF(id_SO2_strat < 0 .OR. id_SO2_strat > nbtr_sulgas) THEN
    176        WRITE(lunout,*) 'ERROR : SO2 index id_SO2_strat=',id_SO2_strat,' is negative or superior than the total sulfur gases !'
    177        CALL abort_physic('strataer_local_var_mod','Wrong SO2 index, check your tracer.def file.',1)
     176      WRITE(lunout, *) 'ERROR : SO2 index id_SO2_strat=', id_SO2_strat, ' is negative or superior than the total sulfur gases !'
     177      CALL abort_physic('strataer_local_var_mod', 'Wrong SO2 index, check your tracer.def file.', 1)
    178178    ELSEIF(id_H2SO4_strat < 0 .OR. id_H2SO4_strat > nbtr_sulgas) THEN
    179        WRITE(lunout,*) 'ERROR : H2SO4 index id_H2SO4_strat=',id_H2SO4_strat,' is negative or superior than the total sulfur gases !'
    180        CALL abort_physic('strataer_local_var_mod','Wrong H2SO4 index, check your tracer.def file.',1)
    181     ENDIF
    182    
     179      WRITE(lunout, *) 'ERROR : H2SO4 index id_H2SO4_strat=', id_H2SO4_strat, ' is negative or superior than the total sulfur gases !'
     180      CALL abort_physic('strataer_local_var_mod', 'Wrong H2SO4 index, check your tracer.def file.', 1)
     181    ENDIF
     182
    183183    !============= Init params =============
    184184    flag_emit = 0                   ! Background (default)
     
    191191    flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No)
    192192    flag_min_rreduce = .TRUE.       ! Minimum lifetime=1.5 pdt phys (default: Yes)
    193     flag_new_strat_compo =.TRUE.    ! H2SO4/H2O weight percent & density routine (default: S. Bekki)
     193    flag_new_strat_compo = .TRUE.    ! H2SO4/H2O weight percent & density routine (default: S. Bekki)
    194194    ok_qemiss = .FALSE.             ! H2O emission flag
    195    
     195
    196196    ! nuc init
    197197    ALPH2SO4 = 0.1
    198198    flag_nuc_rate_box = .FALSE.
    199     nuclat_min=0  ; nuclat_max=0
    200     nucpres_min=0 ; nucpres_max=0
    201    
     199    nuclat_min = 0  ; nuclat_max = 0
     200    nucpres_min = 0 ; nucpres_max = 0
     201
    202202    ! emiss init
    203203    nErupt = 0 ! eruption number
    204204    injdur = 0 ! init injection duration
    205205    nAerErupt = 1 ; nSpeciesErupt = 1
    206     ifreqroc=2 ; flh2o=0
    207    
     206    ifreqroc = 2 ; flh2o = 0
     207
    208208    !============= Read params =============
    209     CALL getin_p('flag_emit',flag_emit)
    210     CALL getin_p('flag_emit_distrib',flag_emit_distrib)
    211     CALL getin_p('flag_verbose_strataer',flag_verbose_strataer)
    212     CALL getin_p('flag_new_nucl',flag_new_nucl)
    213     CALL getin_p('flag_newclim_file',flag_newclim_file)
    214     CALL getin_p('flag_H2O2d_nucleation',flag_H2O2d_nucleation)
    215     CALL getin_p('flag_OH_reduced',flag_OH_reduced)
    216     CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis)
    217     CALL getin_p('flag_min_rreduce',flag_min_rreduce)
    218     CALL getin_p('flag_new_strat_compo',flag_new_strat_compo)
    219     CALL getin_p('ok_qemiss',ok_qemiss)
    220    
     209    CALL getin_p('flag_emit', flag_emit)
     210    CALL getin_p('flag_emit_distrib', flag_emit_distrib)
     211    CALL getin_p('flag_verbose_strataer', flag_verbose_strataer)
     212    CALL getin_p('flag_new_nucl', flag_new_nucl)
     213    CALL getin_p('flag_newclim_file', flag_newclim_file)
     214    CALL getin_p('flag_H2O2d_nucleation', flag_H2O2d_nucleation)
     215    CALL getin_p('flag_OH_reduced', flag_OH_reduced)
     216    CALL getin_p('flag_H2SO4_photolysis', flag_H2SO4_photolysis)
     217    CALL getin_p('flag_min_rreduce', flag_min_rreduce)
     218    CALL getin_p('flag_new_strat_compo', flag_new_strat_compo)
     219    CALL getin_p('ok_qemiss', ok_qemiss)
     220
    221221    !============= Test flag coherence =============
    222222    IF (.NOT. flag_newclim_file) THEN
    223        IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN
    224           WRITE(lunout,*) 'ERROR : flag_newclim_file=',flag_newclim_file, &
    225                ' whereas flag_H2SO4_photolysis=',flag_H2SO4_photolysis,', flag_OH_reduced=',flag_OH_reduced, &
    226                ' and flag_H2O2d_nucleation=',flag_H2O2d_nucleation
    227           CALL abort_physic('strataer_local_var_mod','Incompatible options in physiq_def file !',1)
    228        ENDIF
    229        IF(flag_min_rreduce) THEN
    230           WRITE(lunout,*) 'Warning : flag_min_rreduce will be ignored with old climato file !'
    231        ENDIF
    232     ENDIF
    233    
     223      IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN
     224        WRITE(lunout, *) 'ERROR : flag_newclim_file=', flag_newclim_file, &
     225                ' whereas flag_H2SO4_photolysis=', flag_H2SO4_photolysis, ', flag_OH_reduced=', flag_OH_reduced, &
     226                ' and flag_H2O2d_nucleation=', flag_H2O2d_nucleation
     227        CALL abort_physic('strataer_local_var_mod', 'Incompatible options in physiq_def file !', 1)
     228      ENDIF
     229      IF(flag_min_rreduce) THEN
     230        WRITE(lunout, *) 'Warning : flag_min_rreduce will be ignored with old climato file !'
     231      ENDIF
     232    ENDIF
     233
    234234    !============= Print params =============
    235235    IF (is_master) THEN
    236        WRITE(lunout,*) 'flag_emit = ',flag_emit
    237        WRITE(lunout,*) 'IN STRATAER : flag_new_nucl = ',flag_new_nucl
    238        WRITE(lunout,*) 'IN STRATAER : flag_newclim_file = ',flag_newclim_file
    239        WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib
    240        WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer
    241        IF (flag_emit == 1 .OR. flag_emit == 4) THEN
    242           WRITE(lunout,*) 'IN STRATAER : flag_H2O2d_nucleation = ',flag_H2O2d_nucleation
    243           WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced
    244           WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis
    245           WRITE(lunout,*) 'IN STRATAER : flag_min_rreduce = ',flag_min_rreduce
    246           WRITE(lunout,*) 'IN STRATAER : flag_new_strat_compo = ',flag_new_strat_compo
    247           WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss
    248        ENDIF
     236      WRITE(lunout, *) 'flag_emit = ', flag_emit
     237      WRITE(lunout, *) 'IN STRATAER : flag_new_nucl = ', flag_new_nucl
     238      WRITE(lunout, *) 'IN STRATAER : flag_newclim_file = ', flag_newclim_file
     239      WRITE(lunout, *) 'IN STRATAER : flag_emit_distrib = ', flag_emit_distrib
     240      WRITE(lunout, *) 'IN STRATAER : flag_verbose_strataer = ', flag_verbose_strataer
     241      IF (flag_emit == 1 .OR. flag_emit == 4) THEN
     242        WRITE(lunout, *) 'IN STRATAER : flag_H2O2d_nucleation = ', flag_H2O2d_nucleation
     243        WRITE(lunout, *) 'IN STRATAER : flag_OH_reduced = ', flag_OH_reduced
     244        WRITE(lunout, *) 'IN STRATAER : flag_H2SO4_photolysis = ', flag_H2SO4_photolysis
     245        WRITE(lunout, *) 'IN STRATAER : flag_min_rreduce = ', flag_min_rreduce
     246        WRITE(lunout, *) 'IN STRATAER : flag_new_strat_compo = ', flag_new_strat_compo
     247        WRITE(lunout, *) 'IN STRATAER : ok_qemiss = ', ok_qemiss
     248      ENDIF
    249249    ENDIF ! if master
    250    
     250
    251251    !--initialising dry diameters to geometrically spaced mass/volume (see Jacobson 1994)
    252     mdw(1)=mdwmin
     252    mdw(1) = mdwmin
    253253    IF (V_rat<1.62) THEN ! compensate for dip in second bin for lower volume ratio
    254        mdw(2)=mdw(1)*2.**(1./3.)
    255        DO it=3, nbtr_bin
    256           mdw(it)=mdw(it-1)*V_rat**(1./3.)
    257        ENDDO
     254      mdw(2) = mdw(1) * 2.**(1. / 3.)
     255      DO it = 3, nbtr_bin
     256        mdw(it) = mdw(it - 1) * V_rat**(1. / 3.)
     257      ENDDO
    258258    ELSE
    259        DO it=2, nbtr_bin
    260           mdw(it)=mdw(it-1)*V_rat**(1./3.)
    261        ENDDO
    262     ENDIF
    263     IF (is_master) WRITE(lunout,*) 'init mdw=', mdw
    264    
     259      DO it = 2, nbtr_bin
     260        mdw(it) = mdw(it - 1) * V_rat**(1. / 3.)
     261      ENDDO
     262    ENDIF
     263    IF (is_master) WRITE(lunout, *) 'init mdw=', mdw
     264
    265265    !   compute particle radius RRSI [cm] and volume Vbin [m3] from diameter mdw [m]
    266266    ALLOCATE(RRSI(nbtr_bin), Vbin(nbtr_bin))
    267    
    268     DO it=1,nbtr_bin
    269        !     [cm]
    270        RRSI(it)=mdw(it)/2.*100.
    271        !     [m3]
    272        Vbin(it)=4.0*RPI*((mdw(it)/2.)**3)/3.0
     267
     268    DO it = 1, nbtr_bin
     269      !     [cm]
     270      RRSI(it) = mdw(it) / 2. * 100.
     271      !     [m3]
     272      Vbin(it) = 4.0 * RPI * ((mdw(it) / 2.)**3) / 3.0
    273273    ENDDO
    274    
     274
    275275    IF (is_master) THEN
    276        WRITE(lunout,*) 'init RRSI=', RRSI
    277        WRITE(lunout,*) 'init Vbin=', Vbin
    278     ENDIF
    279    
    280     WRITE(lunout,*) 'IN STRATAER INIT END'
    281    
     276      WRITE(lunout, *) 'init RRSI=', RRSI
     277      WRITE(lunout, *) 'init Vbin=', Vbin
     278    ENDIF
     279
     280    WRITE(lunout, *) 'IN STRATAER INIT END'
     281
    282282  END SUBROUTINE strataer_init
    283  
     283
    284284END MODULE strataer_local_var_mod
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/stratdistrib.F90

    r5087 r5098  
    66  USE dimphy, ONLY : klon,klev
    77  USE strataer_local_var_mod
    8   USE YOMCST, only : RPI
     8  USE lmdz_yomcst, only : RPI
    99
    1010  IMPLICIT NONE
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/stratemit.F90

    r5087 r5098  
    1010  USE phys_cal_mod
    1111  USE phys_local_var_mod, ONLY: d_q_emiss
    12   USE YOMCST, only : RD, RPI, RG
     12  USE lmdz_yomcst, only : RD, RPI, RG
    1313  USE geometry_mod, ONLY : cell_area, boundslat
    1414  USE aerophys
  • LMDZ6/branches/Amaury_dev/libf/phylmd/StratAer/traccoag_mod.F90

    r5087 r5098  
    2424    USE sulfate_aer_mod
    2525    USE phys_local_var_mod, ONLY: stratomask
    26     USE YOMCST
     26    USE lmdz_yomcst
    2727    USE print_control_mod, ONLY: lunout
    2828    USE strataer_local_var_mod
Note: See TracChangeset for help on using the changeset viewer.