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

Last change on this file since 1887 was 1795, checked in by jvatant, 8 years ago

Making Titan's hazy again, part II
+ Added calmufi and inimufi routines that interface YAMMS model
+ Major changes of the tracer gestion in tracer_h (new query by name)
+ Update the deftank
JVO

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