source: trunk/LMDZ.PLUTO/libf/phypluto/mp2m_inimufi.F90 @ 3951

Last change on this file since 3951 was 3951, checked in by debatzbr, 7 weeks ago

Pluto PCM: Add variables, indices, and flags related to microphysical clouds
BBT

File size: 3.8 KB
Line 
1subroutine inimufi(ptimestep)
2  use callkeys_mod, only : call_haze_prod_pCH4, haze_p_prod, haze_tx_prod, haze_rc_prod, &
3                           haze_rm, haze_df, haze_rho, air_rad, &
4                           callmuclouds
5  use tracer_h
6  use comcstfi_mod, only : g, rad, mugaz
7  use datafile_mod
8
9  ! Microphysical model MP2M
10  use mp2m_intgcm
11
12  implicit none
13
14  !============================================================================
15  !
16  !     Purpose
17  !     -------
18  !     This routine call mm_initialize which perform the global initialization
19  !     for the microphysical YAMMS model.
20  !     It also performs some sanity checks on microphysical tracer names.
21  !
22  !     Authors
23  !     -------
24  !     B. de Batz de Trenquelléon (11/2024)
25  !
26  !============================================================================
27
28
29  !----------------
30  ! 0. Declarations
31  !----------------
32
33  integer :: i,idx
34  real, intent(in) :: ptimestep ! Timestep (s)
35
36  character(len=30), dimension(4), parameter :: aernames = &
37     (/"mu_m0as              ", "mu_m3as              ",   &
38       "mu_m0af              ", "mu_m3af              "/)
39 
40  CHARACTER(len=30), DIMENSION(2), PARAMETER :: ccnnames = &
41     (/"mu_m0ccn             ", "mu_m3ccn             "/)
42 
43  logical :: err
44
45  !--------------------------
46  ! 1. Check names of tracers
47  !--------------------------
48  err = .false.
49
50  DO i=1,size(aernames)
51    idx = indexOfTracer(TRIM(aernames(i)),.false.)
52    IF (idx <= 0) THEN
53      WRITE(*,*) "inimufi: '"//TRIM(aernames(i))//"' not found in tracers table."
54      err = .true.
55    ENDIF
56  ENDDO
57
58  IF (callmuclouds) THEN
59    DO i=1,size(ccnnames)
60      idx = indexOfTracer(TRIM(ccnnames(i)),.false.)
61      IF (idx <= 0) THEN
62        WRITE(*,*) "inimufi: '"//TRIM(ccnnames(i))//"' not found in tracers table."
63        err = .true.
64      ENDIF
65    ENDDO
66  ENDIF
67
68  IF (err) THEN
69    WRITE(*,*) "You loose in inimufi.F90.... Try again"
70    STOP
71  ENDIF
72
73  !--------------------------------------------------
74  ! 2. Call microphysical model global initialization
75  !--------------------------------------------------
76 
77  ! /!\ mugaz [g/mol] --> [kg/mol] !!
78  call mm_initialize(ptimestep,call_haze_prod_pCH4,haze_p_prod,haze_tx_prod,haze_rc_prod, &
79                      haze_rm,haze_df,haze_rho,rad,g,air_rad,mugaz*1e-3,                  &
80                      callmuclouds,config_mufi)
81 
82  !-----------------
83  ! 3. Sanity checks
84  !-----------------
85 
86  ! Haze model initialization
87  ! -------------------------
88  write(*,*) 'Number of microphysical tracer nmicro = ',nmicro
89  call dumptracers(micro_indx)
90
91  ! Cloud model initialization
92  ! --------------------------
93  if (callmuclouds) then
94    do i = 1, nmicro_ices
95      ! Setup micro_ice_indx:
96      idx = indexOfTracer("mu_m3"//TRIM(mm_spcname(i)),.false.)
97      if (idx <= 0) then
98        write(*,*) "inimufi: 'mu_m3"//TRIM(mm_spcname(i))//"' not found in tracers table."
99        err = .true.
100      else
101        micro_ice_indx(i) = idx
102      endif
103      ! Setup micro_gas_indx:
104      idx = indexOfTracer(TRIM(mm_spcname(i))//"_mugas",.false.)
105      if (idx <= 0) then
106        write(*,*) "inimufi: '"//TRIM(mm_spcname(i))//"' not found in tracers table."
107        err = .true.
108      else
109        micro_gas_indx(i) = idx
110      endif
111    enddo
112
113    ! Check for errors
114    if (err) then
115      write(*,*) "Error in inimufi: tracer not found in table!"
116      STOP
117    endif
118    if (nmicro_ices.ne.mm_nesp) then
119      write(*,*) "Error in inimufi: nmicro_ices not equal to mm_nesp!"
120      STOP
121    endif
122
123    write(*,*) 'Number of microphysical ice tracer nmicro_ices = ',nmicro_ices
124    write(*,*) 'Ices:'
125    call dumptracers(micro_ice_indx)
126    write(*,*) 'Condensable gases:'
127    call dumptracers(micro_gas_indx)
128  endif ! end of callmuclouds
129 
130end subroutine inimufi
Note: See TracBrowser for help on using the repository browser.