source: LMDZ6/trunk/libf/phylmd/infotrac_phy.F90 @ 3865

Last change on this file since 3865 was 3865, checked in by lmdz-users, 3 years ago

Modifications from Thibaut to create an ESM with interactive CO2 + INCA aerosols

File size: 9.6 KB
Line 
1
2! $Id: $
3
4MODULE infotrac_phy
5
6! Infotrac for physics; for now contains the same information as infotrac for
7! the dynamics (could be further cleaned) and is initialized using values
8! provided by the dynamics
9
10! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
11  INTEGER, SAVE :: nqtot
12!$OMP THREADPRIVATE(nqtot)
13
14!CR: on ajoute le nombre de traceurs de l eau
15  INTEGER, SAVE :: nqo
16!$OMP THREADPRIVATE(nqo)
17
18! nbtr : number of tracers not including higher order of moment or water vapor or liquid
19!        number of tracers used in the physics
20  INTEGER, SAVE :: nbtr
21!$OMP THREADPRIVATE(nbtr)
22
23! ThL : number of tracers specific to INCA
24  INTEGER, SAVE :: nqINCA
25!$OMP THREADPRIVATE(nqINCA)
26
27#ifdef CPP_StratAer
28! nbtr_bin: number of aerosol bins for StratAer model
29! nbtr_sulgas: number of sulfur gases for StratAer model
30  INTEGER, SAVE :: nbtr_bin, nbtr_sulgas
31!$OMP THREADPRIVATE(nbtr_bin,nbtr_sulgas)
32  INTEGER, SAVE :: id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat
33!$OMP THREADPRIVATE(id_OCS_strat, id_SO2_strat, id_H2SO4_strat, id_BIN01_strat)
34#endif
35
36! CRisi: nb traceurs pères= directement advectés par l'air
37  INTEGER, SAVE :: nqperes
38!$OMP THREADPRIVATE(nqperes)
39
40! ThL : nb de traceurs dans le traceur.def
41  INTEGER, SAVE :: nqexcl
42!$OMP THREADPRIVATE(nqexcl)
43
44! Name variables
45  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
46  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
47!$OMP THREADPRIVATE(tname,ttext)
48
49!! iadv  : index of trasport schema for each tracer
50!  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
51
52! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
53!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
54  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
55!$OMP THREADPRIVATE(niadv)
56
57! CRisi: tableaux de fils
58  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqfils
59  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
60  INTEGER, SAVE :: nqdesc_tot
61  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE    :: iqfils
62  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iqpere
63!$OMP THREADPRIVATE(nqfils,nqdesc,nqdesc_tot,iqfils,iqpere)
64
65! conv_flg(it)=0 : convection desactivated for tracer number it
66  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
67!$OMP THREADPRIVATE(conv_flg)
68
69! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
70  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
71!$OMP THREADPRIVATE(pbl_flg)
72
73  CHARACTER(len=4),SAVE :: type_trac
74!$OMP THREADPRIVATE(type_trac)
75  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
76!$OMP THREADPRIVATE(solsym)
77   
78    ! CRisi: cas particulier des isotopes
79    LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
80!$OMP THREADPRIVATE(ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso)
81    INTEGER :: niso_possibles   
82    PARAMETER ( niso_possibles=5)
83    real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
84!$OMP THREADPRIVATE(tnat,alpha_ideal)
85    LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
86!$OMP THREADPRIVATE(use_iso)
87    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
88!$OMP THREADPRIVATE(iqiso)
89    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
90!$OMP THREADPRIVATE(iso_num)
91    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
92!$OMP THREADPRIVATE(iso_indnum)
93    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
94!$OMP THREADPRIVATE(zone_num)
95    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
96!$OMP THREADPRIVATE(phase_num)
97    INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numéro d isotope entre 1 et niso_possibles
98!$OMP THREADPRIVATE(indnum_fn_num)
99    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
100!$OMP THREADPRIVATE(index_trac)
101    INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
102!$OMP THREADPRIVATE(niso,ntraceurs_zone,ntraciso)
103 
104CONTAINS
105
106  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqINCA_,tname_,ttext_,type_trac_,&
107                               niadv_,conv_flg_,pbl_flg_,solsym_,&
108                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
109                               ok_isotopes_,ok_iso_verif_,ok_isotrac_,&
110                               ok_init_iso_,niso_possibles_,tnat_,&
111                               alpha_ideal_,use_iso_,iqiso_,iso_num_,&
112                               iso_indnum_,zone_num_,phase_num_,&
113                               indnum_fn_num_,index_trac_,&
114                               niso_,ntraceurs_zone_,ntraciso_&
115#ifdef CPP_StratAer
116                               ,nbtr_bin_,nbtr_sulgas_&
117                               ,id_OCS_strat_,id_SO2_strat_,id_H2SO4_strat_,id_BIN01_strat_&
118#endif
119                               )
120
121    ! transfer information on tracers from dynamics to physics
122    USE print_control_mod, ONLY: prt_level, lunout
123    IMPLICIT NONE
124
125    INTEGER,INTENT(IN) :: nqtot_
126    INTEGER,INTENT(IN) :: nqo_
127    INTEGER,INTENT(IN) :: nbtr_
128    INTEGER,INTENT(IN) :: nqINCA_
129#ifdef CPP_StratAer
130    INTEGER,INTENT(IN) :: nbtr_bin_
131    INTEGER,INTENT(IN) :: nbtr_sulgas_
132    INTEGER,INTENT(IN) :: id_OCS_strat_
133    INTEGER,INTENT(IN) :: id_SO2_strat_
134    INTEGER,INTENT(IN) :: id_H2SO4_strat_
135    INTEGER,INTENT(IN) :: id_BIN01_strat_
136#endif
137    CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
138    CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
139    CHARACTER(len=4),INTENT(IN) :: type_trac_
140    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
141    INTEGER,INTENT(IN) :: conv_flg_(nqINCA_)
142    INTEGER,INTENT(IN) :: pbl_flg_(nqINCA_)
143    CHARACTER(len=8),INTENT(IN) :: solsym_(nqINCA_)
144    ! Isotopes:
145    INTEGER,INTENT(IN) :: nqfils_(nqtot_)
146    INTEGER,INTENT(IN) :: nqdesc_(nqtot_)
147    INTEGER,INTENT(IN) :: nqdesc_tot_
148    INTEGER,INTENT(IN) :: iqfils_(nqtot_,nqtot_)
149    INTEGER,INTENT(IN) :: iqpere_(nqtot_)
150    LOGICAL,INTENT(IN) :: ok_isotopes_
151    LOGICAL,INTENT(IN) :: ok_iso_verif_
152    LOGICAL,INTENT(IN) :: ok_isotrac_
153    LOGICAL,INTENT(IN) :: ok_init_iso_
154    INTEGER,INTENT(IN) :: niso_possibles_
155    REAL,INTENT(IN) :: tnat_(niso_possibles_)
156    REAL,INTENT(IN) :: alpha_ideal_(niso_possibles_)
157    LOGICAL,INTENT(IN) :: use_iso_(niso_possibles_)
158    INTEGER,INTENT(IN) :: iqiso_(ntraciso_,nqo_)
159    INTEGER,INTENT(IN) :: iso_num_(nqtot_)
160    INTEGER,INTENT(IN) :: iso_indnum_(nqtot_)
161    INTEGER,INTENT(IN) :: zone_num_(nqtot_)
162    INTEGER,INTENT(IN) :: phase_num_(nqtot_)
163    INTEGER,INTENT(IN) :: indnum_fn_num_(niso_possibles_)
164    INTEGER,INTENT(IN) :: index_trac_(ntraceurs_zone_,niso_)
165    INTEGER,INTENT(IN) :: niso_
166    INTEGER,INTENT(IN) :: ntraceurs_zone_
167    INTEGER,INTENT(IN) :: ntraciso_
168
169    CHARACTER(LEN=30) :: modname="init_infotrac_phy"
170
171    nqtot=nqtot_
172    nqo=nqo_
173    nbtr=nbtr_
174    nqINCA=nqINCA_
175#ifdef CPP_StratAer
176    nbtr_bin=nbtr_bin_
177    nbtr_sulgas=nbtr_sulgas_
178    id_OCS_strat=id_OCS_strat_
179    id_SO2_strat=id_SO2_strat_
180    id_H2SO4_strat=id_H2SO4_strat_
181    id_BIN01_strat=id_BIN01_strat_
182#endif
183    ALLOCATE(tname(nqtot))
184    tname(:) = tname_(:)
185    ALLOCATE(ttext(nqtot))
186    ttext(:) = ttext_(:)
187    type_trac = type_trac_
188    ALLOCATE(niadv(nqtot))
189    niadv(:)=niadv_(:)
190    ALLOCATE(conv_flg(nbtr))
191    IF (type_trac == 'inco') THEN
192      conv_flg(1)=1
193      conv_flg(2:nbtr)=conv_flg_(:)
194    ELSE
195      conv_flg(:)=conv_flg_(:)
196    ENDIF
197    ALLOCATE(pbl_flg(nbtr))
198    IF (type_trac == 'inco') THEN
199      pbl_flg(1)=1
200      pbl_flg(2:nbtr)=pbl_flg_(:)
201    ELSE
202      pbl_flg(:)=pbl_flg_(:)
203    ENDIF
204    ALLOCATE(solsym(nbtr))
205    IF (type_trac == 'inco') THEN
206      solsym(1)='CO2'
207      solsym(2:nbtr)=solsym_(:)
208    ELSE
209      solsym(:)=solsym_(:)
210    ENDIF
211     
212    IF(prt_level.ge.1) THEN
213      write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqINCA",nqtot,nqo,nbtr,nqINCA
214    ENDIF
215   
216    ! Isotopes:
217   
218    ! First check that the "niso_possibles" has the correct value
219    IF (niso_possibles.ne.niso_possibles_) THEN
220      CALL abort_physic(modname,&
221           "wrong value for parameter niso_possibles in infotrac_phy",1)
222    ENDIF
223   
224    ok_isotopes=ok_isotopes_
225    ok_iso_verif=ok_iso_verif_
226    ok_isotrac=ok_isotrac_
227    ok_init_iso=ok_init_iso_
228   
229    niso=niso_
230    ntraceurs_zone=ntraceurs_zone_
231    ntraciso=ntraciso_
232   
233    IF (ok_isotopes) THEN
234      ALLOCATE(nqfils(nqtot))
235      nqfils(:)=nqfils_(:)
236      ALLOCATE(nqdesc(nqtot))
237      nqdesc(:)=nqdesc_(:)
238      nqdesc_tot=nqdesc_tot_
239      ALLOCATE(iqfils(nqtot,nqtot))
240      iqfils(:,:)=iqfils_(:,:)
241      ALLOCATE(iqpere(nqtot))
242      iqpere(:)=iqpere_(:)
243   
244      tnat(:)=tnat_(:)
245      alpha_ideal(:)=alpha_ideal_(:)
246      use_iso(:)=use_iso_(:)
247   
248      ALLOCATE(iqiso(ntraciso,nqo))
249      iqiso(:,:)=iqiso_(:,:)
250      ALLOCATE(iso_num(nqtot))
251      iso_num(:)=iso_num_(:)
252      ALLOCATE(iso_indnum(nqtot))
253      iso_indnum(:)=iso_indnum_(:)
254      ALLOCATE(zone_num(nqtot))
255      zone_num(:)=zone_num_(:)
256      ALLOCATE(phase_num(nqtot))
257      phase_num(:)=phase_num_(:)
258     
259      indnum_fn_num(:)=indnum_fn_num_(:)
260     
261      ALLOCATE(index_trac(ntraceurs_zone,niso))
262      index_trac(:,:)=index_trac_(:,:)
263    ENDIF ! of IF(ok_isotopes)
264 
265  END SUBROUTINE init_infotrac_phy
266
267END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.