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

Last change on this file since 3000 was 2369, checked in by jvatant, 5 years ago

Titan GCM: Enable to switch off microphysics compiling for old compilo such as CICLAD, in this case just use -cpp OLD_COMPILO in your makelmdz_fcm

  • Property svn:executable set to *
File size: 2.7 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  !
26  !============================================================================
27
28
29  !--------------------------
30  ! 0. Declarations
31  ! -------------------------
32
33  real, intent(in)                   :: ptimestep    ! Timestep (s)
34
35  integer :: i,idx
36  character(len=30), dimension(4), parameter :: aernames = &
37     (/"mu_m0as              ", "mu_m3as              ",   &
38       "mu_m0af              ", "mu_m3af              "/)
39  CHARACTER(len=30), DIMENSION(2), PARAMETER :: ccnnames = &
40     (/"mu_m0n               ", "mu_m3n               "/)
41  logical :: err
42
43  ! PATCH : YAMMS now allows to enable/disable effective g computations:
44  mm_use_effg = eff_gz
45
46  !----------------------------------------------------
47  ! 1. Call microphysical model global initialization
48  ! ---------------------------------------------------
49
50  ! enable log for what it's worth...
51  ! mm_log = .true.
52 
53  call mmp_initialize(ptimestep,p_prod,tx_prod,rc_prod, &
54        rad,g,air_rad,mugaz,callclouds,config_mufi)
55
56   ! -------------------------
57   ! 2. Check names of tracers
58   ! -------------------------
59   err = .false.
60   DO i=1,size(aernames)
61     idx = indexOfTracer(TRIM(aernames(i)),.false.)
62     IF (idx <= 0) THEN
63       WRITE(*,*) "inimufi: '"//TRIM(aernames(i))//"' not found in tracers table."
64       err = .true.
65     ENDIF
66   ENDDO
67   IF (callclouds) THEN
68     DO i=1,size(ccnnames)
69       idx = indexOfTracer(TRIM(ccnnames(i)),.false.)
70       IF (idx <= 0) THEN
71         WRITE(*,*) "inimufi: '"//TRIM(ccnnames(i))//"' not found in tracers table."
72         err = .true.
73       ENDIF
74     ENDDO
75     ALLOCATE(ices_indx(mm_nesp))
76     ices_indx(:) = -1
77     DO i=1,mm_nesp
78       idx = indexOfTracer("mu_m3"//TRIM(mm_spcname(i)),.false.)
79       IF (idx <= 0) THEN
80         WRITE(*,*) "inimufi: 'mu_m3"//TRIM(mm_spcname(i))//"' not found in tracers table."
81         err = .true.
82       ELSE
83         ices_indx(i) = idx
84       ENDIF
85     ENDDO
86     IF (err) THEN
87       WRITE(*,*) "You loose.... Try again"
88       STOP
89     ENDIF
90   ENDIF
91
92#endif
93
94end subroutine inimufi
Note: See TracBrowser for help on using the repository browser.