source: LMDZ6/trunk/libf/phylmd/StratAer/strataer_nuc_mod.F90 @ 4601

Last change on this file since 4601 was 4601, checked in by dcugnet, 11 months ago

StratAer? commit, N. Lebas

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