Ignore:
Timestamp:
Dec 9, 2025, 3:08:05 PM (9 hours ago)
Author:
lebasn
Message:

StratAer?: remove old params and rename others for coherence (flag_nucl and flag_strat_compo). Use integer instead of boolean to choose compo and nucleation methods.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/StratAer/strataer_local_var_mod.f90

    r5652 r5924  
    1414  !$OMP THREADPRIVATE(flag_emit_distrib)
    1515 
    16   ! 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)
    18   !$OMP THREADPRIVATE(flag_new_nucl)
    19  
    20   ! Use relative humidity from 2D model stratospheric H2O because LMDz is too dry in the stratosphere
    21   ! (no CH4 oxidation)
    22   LOGICAL,SAVE :: flag_H2O2d_nucleation
    23   !$OMP THREADPRIVATE(flag_H2O2d_nucleation)
     16  ! flag to choose nucleation method
     17  INTEGER,SAVE :: flag_nucl   ! 1: routine from H. Vehkamäki (FMI), 2: routine from A. Maattanen (LATMOS)
     18  !$OMP THREADPRIVATE(flag_nucl)
    2419 
    2520  ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction
     
    3328  !$OMP THREADPRIVATE(flag_H2SO4_photolysis)
    3429 
    35   ! flag for minimum lifetime (=1.5 pdt phys)
    36   LOGICAL,SAVE :: flag_min_rreduce
    37   !$OMP THREADPRIVATE(flag_min_rreduce)
    38  
    39   ! flag to read new climato (O3, H2O & H2SO4_LIFET)
    40   LOGICAL,SAVE :: flag_newclim_file
    41   !$OMP THREADPRIVATE(flag_newclim_file)
    42  
    43   ! flag to choose new H2SO4 density and weight percent from Tabazadeh et al. (1994).
    44   LOGICAL,SAVE :: flag_new_strat_compo
    45   !$OMP THREADPRIVATE(flag_new_strat_compo)
     30  ! Parameterization method to compute H2SO4/H2O aerosol composition
     31  INTEGER,SAVE :: flag_strat_compo  !  1: S. Bekki et al., 2: Tabazadeh et al. 1997
     32  !$OMP THREADPRIVATE(flag_strat_compo)
    4633 
    4734  ! Verbose mode to get more print info
     
    184171    flag_emit = 0                   ! Background (default)
    185172    flag_emit_distrib = 0           ! Gaussian (default)
    186     flag_new_nucl = .TRUE.          ! Define nucleation routine (default: A. Maattanen - LATMOS)
     173    flag_nucl = 2                   ! Define nucleation routine (default: A. Maattanen - LATMOS)
    187174    flag_verbose_strataer = .FALSE. ! verbose mode
    188     flag_newclim_file = .TRUE.      ! Define input climato file (default: all climato)
    189     flag_H2O2d_nucleation = .FALSE. ! Use H2O 2D climato (default: No)
    190175    flag_OH_reduced = .FALSE.       ! OH reduce (default: No)
    191176    flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No)
    192     flag_min_rreduce = .TRUE.       ! Minimum lifetime=1.5 pdt phys (default: Yes)
    193     flag_new_strat_compo =.FALSE.   ! H2SO4/H2O weight percent & density routine (default: S. Bekki)
     177    flag_strat_compo = 2            ! H2SO4/H2O composition routine (default: Tabazadeh et al. 1997)
    194178    ok_qemiss = .FALSE.             ! H2O emission flag
    195179   
     
    219203    CALL getin_p('flag_emit_distrib',flag_emit_distrib)
    220204    CALL getin_p('flag_verbose_strataer',flag_verbose_strataer)
    221     CALL getin_p('flag_new_nucl',flag_new_nucl)
    222     CALL getin_p('flag_newclim_file',flag_newclim_file)
    223     CALL getin_p('flag_H2O2d_nucleation',flag_H2O2d_nucleation)
     205    CALL getin_p('flag_nucl',flag_nucl)
    224206    CALL getin_p('flag_OH_reduced',flag_OH_reduced)
    225207    CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis)
    226     CALL getin_p('flag_min_rreduce',flag_min_rreduce)
    227     CALL getin_p('flag_new_strat_compo',flag_new_strat_compo)
     208    CALL getin_p('flag_strat_compo',flag_strat_compo)
    228209    CALL getin_p('ok_qemiss',ok_qemiss)
    229    
    230     !============= Test flag coherence =============
    231     IF (.NOT. flag_newclim_file) THEN
    232        IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN
    233           WRITE(lunout,*) 'ERROR : flag_newclim_file=',flag_newclim_file, &
    234                ' whereas flag_H2SO4_photolysis=',flag_H2SO4_photolysis,', flag_OH_reduced=',flag_OH_reduced, &
    235                ' and flag_H2O2d_nucleation=',flag_H2O2d_nucleation
    236           CALL abort_physic('strataer_local_var_mod','Incompatible options in physiq_def file !',1)
    237        ENDIF
    238        IF(flag_min_rreduce) THEN
    239           WRITE(lunout,*) 'Warning : flag_min_rreduce will be ignored with old climato file !'
    240        ENDIF
    241     ENDIF
    242210   
    243211    !============= Print params =============
    244212    IF (is_master) THEN
    245213       WRITE(lunout,*) 'flag_emit = ',flag_emit
    246        WRITE(lunout,*) 'IN STRATAER : flag_new_nucl = ',flag_new_nucl
    247        WRITE(lunout,*) 'IN STRATAER : flag_newclim_file = ',flag_newclim_file
     214       WRITE(lunout,*) 'IN STRATAER : flag_nucl = ',flag_nucl
    248215       WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib
    249216       WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer
    250217       IF (flag_emit == 1 .OR. flag_emit == 4) THEN
    251           WRITE(lunout,*) 'IN STRATAER : flag_H2O2d_nucleation = ',flag_H2O2d_nucleation
    252218          WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced
    253219          WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis
    254           WRITE(lunout,*) 'IN STRATAER : flag_min_rreduce = ',flag_min_rreduce
    255           WRITE(lunout,*) 'IN STRATAER : flag_new_strat_compo = ',flag_new_strat_compo
     220          WRITE(lunout,*) 'IN STRATAER : flag_strat_compo = ',flag_strat_compo
    256221          WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss
    257222       ENDIF
Note: See TracChangeset for help on using the changeset viewer.