[4601] | 1 | ! $Id: strataer_nuc_mod.F90 3930 2021-06-11 19:39:09Z oboucher $ |
---|
| 2 | MODULE strataer_nuc_mod |
---|
| 3 | ! This module contains information about strato microphysic model nucleation parameters |
---|
| 4 | |
---|
| 5 | IMPLICIT NONE |
---|
| 6 | |
---|
| 7 | CONTAINS |
---|
| 8 | |
---|
| 9 | ! Init all nucleation params |
---|
| 10 | SUBROUTINE strataer_nuc_init() |
---|
| 11 | |
---|
| 12 | USE ioipsl_getin_p_mod, ONLY : getin_p |
---|
| 13 | USE print_control_mod, ONLY : lunout |
---|
| 14 | USE mod_phys_lmdz_para, ONLY : is_master |
---|
[4950] | 15 | USE strataer_local_var_mod, ONLY: ALPH2SO4,flag_nuc_rate_box,nuclat_min,nuclat_max, & |
---|
| 16 | nucpres_min,nucpres_max |
---|
[4601] | 17 | |
---|
| 18 | !Config Key = flag_nuc_rate_box |
---|
| 19 | !Config Desc = define or not a box for nucleation rate |
---|
| 20 | ! - F = global nucleation |
---|
| 21 | ! - T = 2D-box for nucleation need nuclat_min, nuclat_max, nucpres_min and |
---|
| 22 | ! nucpres_max |
---|
| 23 | ! to define its bounds. |
---|
| 24 | !Config Def = F |
---|
| 25 | !Config Help = Used in physiq.F |
---|
| 26 | ! |
---|
| 27 | CALL getin_p('flag_nuc_rate_box',flag_nuc_rate_box) |
---|
| 28 | CALL getin_p('nuclat_min',nuclat_min) |
---|
| 29 | CALL getin_p('nuclat_max',nuclat_max) |
---|
| 30 | CALL getin_p('nucpres_min',nucpres_min) |
---|
| 31 | CALL getin_p('nucpres_max',nucpres_max) |
---|
| 32 | |
---|
[4950] | 33 | ! Read argument H2SO4 accommodation coefficient [condensation/evaporation] |
---|
| 34 | CALL getin_p('alph2so4',ALPH2SO4) |
---|
| 35 | |
---|
[4601] | 36 | !============= Print params ============= |
---|
| 37 | IF (is_master) THEN |
---|
[4950] | 38 | WRITE(lunout,*) 'IN STRATAER_NUC : ALPH2SO4 = ',alph2so4 |
---|
[4601] | 39 | WRITE(lunout,*) 'IN STRATAER_NUC : flag_nuc_rate_box = ',flag_nuc_rate_box |
---|
| 40 | IF (flag_nuc_rate_box) THEN |
---|
| 41 | WRITE(lunout,*) 'IN STRATAER_NUC : nuclat_min = ',nuclat_min,', nuclat_max = ',nuclat_max |
---|
| 42 | WRITE(lunout,*) 'IN STRATAER_NUC : nucpres_min = ',nucpres_min,', nucpres_max = ',nucpres_max |
---|
| 43 | ENDIF |
---|
| 44 | ENDIF ! if master |
---|
| 45 | |
---|
| 46 | END SUBROUTINE strataer_nuc_init |
---|
| 47 | |
---|
| 48 | ! Init aerosol tracers and large scale scavinging |
---|
| 49 | SUBROUTINE tracstrataer_init(aerosol,lessivage) |
---|
| 50 | |
---|
| 51 | USE infotrac_phy, ONLY: nbtr, nbtr_sulgas, id_H2SO4_strat |
---|
| 52 | USE ioipsl, ONLY : getin |
---|
| 53 | USE print_control_mod, ONLY : lunout |
---|
| 54 | |
---|
| 55 | ! Output variables |
---|
| 56 | LOGICAL,DIMENSION(nbtr), INTENT(INOUT) :: aerosol |
---|
| 57 | LOGICAL,INTENT(INOUT) :: lessivage |
---|
| 58 | INTEGER :: it |
---|
| 59 | |
---|
| 60 | ! Initialization |
---|
| 61 | lessivage =.TRUE. |
---|
| 62 | aerosol(:) = .FALSE. |
---|
| 63 | |
---|
| 64 | DO it= 1, nbtr_sulgas |
---|
| 65 | aerosol(it)=.FALSE. |
---|
| 66 | IF (it==id_H2SO4_strat) aerosol(it)=.TRUE. |
---|
| 67 | ENDDO |
---|
| 68 | DO it= nbtr_sulgas+1, nbtr |
---|
| 69 | aerosol(it)=.TRUE. |
---|
| 70 | ENDDO |
---|
| 71 | |
---|
| 72 | !!jyg(20130206) : le choix d activation du lessivage est fait dans phytrac avec iflag_lscav |
---|
| 73 | ! CALL getin('lessivage',lessivage) |
---|
| 74 | WRITE(lunout,*) 'IN TRACSTRATAER_INIT lessivage: ',lessivage |
---|
| 75 | |
---|
| 76 | END SUBROUTINE tracstrataer_init |
---|
| 77 | |
---|
| 78 | END MODULE strataer_nuc_mod |
---|