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

Last change on this file since 2236 was 1984, checked in by jvatant, 6 years ago

Follow-up of r1971 r1978 and r1980 on tracers name lenght.
--JVO

  • Property svn:executable set to *
File size: 2.6 KB
Line 
1subroutine inimufi(ptimestep)
2
3  use mmp_gcm
4  use callkeys_mod, only : callclouds, p_prod, tx_prod, rc_prod, air_rad, eff_gz
5  use tracer_h
6  use comcstfi_mod, only : g, rad, mugaz
7  use datafile_mod
8
9  implicit none
10
11
12  !============================================================================
13  !
14  !     Purpose
15  !     -------
16  !     This routine call mm_initialize which perform the global initialization
17  !     for the microphysical YAMMS model.
18  !     It also performs some sanity checks on microphysical tracer names.
19  !
20  !     Authors
21  !     -------
22  !     J. Vatant d'Ollone, J.Burgalat, S.Lebonnois (09/2017)
23  !
24  !============================================================================
25
26
27  !--------------------------
28  ! 0. Declarations
29  ! -------------------------
30
31  real, intent(in)                   :: ptimestep    ! Timestep (s)
32
33  integer :: i,idx
34  character(len=30), dimension(4), parameter :: aernames = &
35     (/"mu_m0as              ", "mu_m3as              ",   &
36       "mu_m0af              ", "mu_m3af              "/)
37  CHARACTER(len=30), DIMENSION(2), PARAMETER :: ccnnames = &
38     (/"mu_m0n               ", "mu_m3n               "/)
39  logical :: err
40
41  ! PATCH : YAMMS now allows to enable/disable effective g computations:
42  mm_use_effg = eff_gz
43
44  !----------------------------------------------------
45  ! 1. Call microphysical model global initialization
46  ! ---------------------------------------------------
47
48  ! enable log for what it's worth...
49  ! mm_log = .true.
50 
51  call mmp_initialize(ptimestep,p_prod,tx_prod,rc_prod, &
52        rad,g,air_rad,mugaz,callclouds,config_mufi)
53
54   ! -------------------------
55   ! 2. Check names of tracers
56   ! -------------------------
57   err = .false.
58   DO i=1,size(aernames)
59     idx = indexOfTracer(TRIM(aernames(i)),.false.)
60     IF (idx <= 0) THEN
61       WRITE(*,*) "inimufi: '"//TRIM(aernames(i))//"' not found in tracers table."
62       err = .true.
63     ENDIF
64   ENDDO
65   IF (callclouds) THEN
66     DO i=1,size(ccnnames)
67       idx = indexOfTracer(TRIM(ccnnames(i)),.false.)
68       IF (idx <= 0) THEN
69         WRITE(*,*) "inimufi: '"//TRIM(ccnnames(i))//"' not found in tracers table."
70         err = .true.
71       ENDIF
72     ENDDO
73     ALLOCATE(ices_indx(mm_nesp))
74     ices_indx(:) = -1
75     DO i=1,mm_nesp
76       idx = indexOfTracer("mu_m3"//TRIM(mm_spcname(i)),.false.)
77       IF (idx <= 0) THEN
78         WRITE(*,*) "inimufi: 'mu_m3"//TRIM(mm_spcname(i))//"' not found in tracers table."
79         err = .true.
80       ELSE
81         ices_indx(i) = idx
82       ENDIF
83     ENDDO
84     IF (err) THEN
85       WRITE(*,*) "You loose.... Try again"
86       STOP
87     ENDIF
88   ENDIF
89
90end subroutine inimufi
Note: See TracBrowser for help on using the repository browser.