source: trunk/LMDZ.TITAN/libf/phytitan/inimufi.F90 @ 3529

Last change on this file since 3529 was 3090, checked in by slebonnois, 14 months ago

BdeBatz? : Cleans microphysics and makes few corrections for physics

  • Property svn:executable set to *
File size: 3.3 KB
Line 
1subroutine inimufi(ptimestep)
2
3#ifndef OLD_COMPILO
4
5  use mmp_gcm
6  use callkeys_mod, only : callclouds, p_prod, tx_prod, rc_prod, air_rad, eff_gz
7  use tracer_h
8  use comcstfi_mod, only : g, rad, mugaz
9  use datafile_mod
10
11  implicit none
12
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  !     J. Vatant d'Ollone, J.Burgalat, S.Lebonnois (09/2017)
25  !     Modified : B. de Batz de Trenquelléon (02/2023)
26  !
27  !============================================================================
28
29
30  !--------------------------
31  ! 0. Declarations
32  ! -------------------------
33
34  real, intent(in)                   :: ptimestep    ! Timestep (s)
35
36  integer :: i,idx
37  character(len=30), dimension(4), parameter :: aernames = &
38     (/"mu_m0as              ", "mu_m3as              ",   &
39       "mu_m0af              ", "mu_m3af              "/)
40  CHARACTER(len=30), DIMENSION(2), PARAMETER :: ccnnames = &
41     (/"mu_m0n               ", "mu_m3n               "/)
42  logical :: err
43
44  ! PATCH : YAMMS now allows to enable/disable effective g computations:
45  mm_use_effg = eff_gz
46
47  !----------------------------------------------------
48  ! 1. Call microphysical model global initialization
49  ! ---------------------------------------------------
50
51  ! enable log for what it's worth...
52  ! mm_log = .true.
53 
54  call mmp_initialize(ptimestep,p_prod,tx_prod,rc_prod, &
55        rad,g,air_rad,mugaz,callclouds,config_mufi)
56
57   ! -------------------------
58   ! 2. Check names of tracers
59   ! -------------------------
60   err = .false.
61   DO i=1,size(aernames)
62     idx = indexOfTracer(TRIM(aernames(i)),.false.)
63     IF (idx <= 0) THEN
64       WRITE(*,*) "inimufi: '"//TRIM(aernames(i))//"' not found in tracers table."
65       err = .true.
66     ENDIF
67   ENDDO
68   IF (callclouds) THEN
69     DO i=1,size(ccnnames)
70       idx = indexOfTracer(TRIM(ccnnames(i)),.false.)
71       IF (idx <= 0) THEN
72         WRITE(*,*) "inimufi: '"//TRIM(ccnnames(i))//"' not found in tracers table."
73         err = .true.
74       ENDIF
75     ENDDO
76     
77     nice = mm_nesp
78
79     ALLOCATE(ices_indx(mm_nesp))
80     ALLOCATE(gazs_indx(mm_nesp))
81     ices_indx(:) = -1
82     gazs_indx(:) = -1
83     DO i=1,mm_nesp
84       idx = indexOfTracer("mu_m3"//TRIM(mm_spcname(i)),.false.)
85       IF (idx <= 0) THEN
86         WRITE(*,*) "inimufi: 'mu_m3"//TRIM(mm_spcname(i))//"' not found in tracers table."
87         err = .true.
88       ELSE
89         ices_indx(i) = idx
90       ENDIF
91
92       idx = indexOfTracer(TRIM(mm_spcname(i)),.false.)
93       IF (idx <= 0) THEN
94         WRITE(*,*) "inimufi: '"//TRIM(mm_spcname(i))//"' not found in tracers table."
95         err = .true.
96       ELSE
97         gazs_indx(i) = idx
98       ENDIF
99     ENDDO
100
101     IF (err) THEN
102       WRITE(*,*) "You loose.... Try again"
103       STOP
104     ENDIF
105     
106     write(*,*) 'DUMPTRACERS - MICRO_INDX'
107     call dumpTracers(micro_indx)
108     write(*,*) 'DUMPTRACERS - ICES_INDX'
109     call dumpTracers(ices_indx)
110     write(*,*) 'DUMPTRACERS - GAZS_INDX'
111     call dumpTracers(gazs_indx)
112   ENDIF
113   
114#endif
115
116end subroutine inimufi
Note: See TracBrowser for help on using the repository browser.