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

Last change on this file since 3872 was 3872, checked in by oboucher, 3 years ago

Last modifications for the CO2/INCA (inco) case

File size: 9.2 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 CO2 tracers                   ModThL
24  INTEGER, SAVE :: nqCO2
25!$OMP THREADPRIVATE(nqCO2)
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! Name variables
41  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
42  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
43!$OMP THREADPRIVATE(tname,ttext)
44
45!! iadv  : index of trasport schema for each tracer
46!  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
47
48! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
49!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
50  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
51!$OMP THREADPRIVATE(niadv)
52
53! CRisi: tableaux de fils
54  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqfils
55  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
56  INTEGER, SAVE :: nqdesc_tot
57  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE    :: iqfils
58  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iqpere
59!$OMP THREADPRIVATE(nqfils,nqdesc,nqdesc_tot,iqfils,iqpere)
60
61! conv_flg(it)=0 : convection desactivated for tracer number it
62  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
63!$OMP THREADPRIVATE(conv_flg)
64
65! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
66  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
67!$OMP THREADPRIVATE(pbl_flg)
68
69  CHARACTER(len=4),SAVE :: type_trac
70!$OMP THREADPRIVATE(type_trac)
71  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
72!$OMP THREADPRIVATE(solsym)
73   
74    ! CRisi: cas particulier des isotopes
75    LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
76!$OMP THREADPRIVATE(ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso)
77    INTEGER :: niso_possibles   
78    PARAMETER ( niso_possibles=5)
79    real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
80!$OMP THREADPRIVATE(tnat,alpha_ideal)
81    LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
82!$OMP THREADPRIVATE(use_iso)
83    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
84!$OMP THREADPRIVATE(iqiso)
85    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
86!$OMP THREADPRIVATE(iso_num)
87    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
88!$OMP THREADPRIVATE(iso_indnum)
89    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
90!$OMP THREADPRIVATE(zone_num)
91    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
92!$OMP THREADPRIVATE(phase_num)
93    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
94!$OMP THREADPRIVATE(indnum_fn_num)
95    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
96!$OMP THREADPRIVATE(index_trac)
97    INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
98!$OMP THREADPRIVATE(niso,ntraceurs_zone,ntraciso)
99 
100CONTAINS
101
102  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqCO2_,tname_,ttext_,type_trac_,&
103                               niadv_,conv_flg_,pbl_flg_,solsym_,&
104                               nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
105                               ok_isotopes_,ok_iso_verif_,ok_isotrac_,&
106                               ok_init_iso_,niso_possibles_,tnat_,&
107                               alpha_ideal_,use_iso_,iqiso_,iso_num_,&
108                               iso_indnum_,zone_num_,phase_num_,&
109                               indnum_fn_num_,index_trac_,&
110                               niso_,ntraceurs_zone_,ntraciso_&
111#ifdef CPP_StratAer
112                               ,nbtr_bin_,nbtr_sulgas_&
113                               ,id_OCS_strat_,id_SO2_strat_,id_H2SO4_strat_,id_BIN01_strat_&
114#endif
115                               )
116
117    ! transfer information on tracers from dynamics to physics
118    USE print_control_mod, ONLY: prt_level, lunout
119    IMPLICIT NONE
120
121    INTEGER,INTENT(IN) :: nqtot_
122    INTEGER,INTENT(IN) :: nqo_
123    INTEGER,INTENT(IN) :: nbtr_
124    INTEGER,INTENT(IN) :: nqCO2_
125#ifdef CPP_StratAer
126    INTEGER,INTENT(IN) :: nbtr_bin_
127    INTEGER,INTENT(IN) :: nbtr_sulgas_
128    INTEGER,INTENT(IN) :: id_OCS_strat_
129    INTEGER,INTENT(IN) :: id_SO2_strat_
130    INTEGER,INTENT(IN) :: id_H2SO4_strat_
131    INTEGER,INTENT(IN) :: id_BIN01_strat_
132#endif
133    CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
134    CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
135    CHARACTER(len=4),INTENT(IN) :: type_trac_
136    INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
137    INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
138    INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)
139    CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)
140    ! Isotopes:
141    INTEGER,INTENT(IN) :: nqfils_(nqtot_)
142    INTEGER,INTENT(IN) :: nqdesc_(nqtot_)
143    INTEGER,INTENT(IN) :: nqdesc_tot_
144    INTEGER,INTENT(IN) :: iqfils_(nqtot_,nqtot_)
145    INTEGER,INTENT(IN) :: iqpere_(nqtot_)
146    LOGICAL,INTENT(IN) :: ok_isotopes_
147    LOGICAL,INTENT(IN) :: ok_iso_verif_
148    LOGICAL,INTENT(IN) :: ok_isotrac_
149    LOGICAL,INTENT(IN) :: ok_init_iso_
150    INTEGER,INTENT(IN) :: niso_possibles_
151    REAL,INTENT(IN) :: tnat_(niso_possibles_)
152    REAL,INTENT(IN) :: alpha_ideal_(niso_possibles_)
153    LOGICAL,INTENT(IN) :: use_iso_(niso_possibles_)
154    INTEGER,INTENT(IN) :: iqiso_(ntraciso_,nqo_)
155    INTEGER,INTENT(IN) :: iso_num_(nqtot_)
156    INTEGER,INTENT(IN) :: iso_indnum_(nqtot_)
157    INTEGER,INTENT(IN) :: zone_num_(nqtot_)
158    INTEGER,INTENT(IN) :: phase_num_(nqtot_)
159    INTEGER,INTENT(IN) :: indnum_fn_num_(niso_possibles_)
160    INTEGER,INTENT(IN) :: index_trac_(ntraceurs_zone_,niso_)
161    INTEGER,INTENT(IN) :: niso_
162    INTEGER,INTENT(IN) :: ntraceurs_zone_
163    INTEGER,INTENT(IN) :: ntraciso_
164
165    CHARACTER(LEN=30) :: modname="init_infotrac_phy"
166
167    nqtot=nqtot_
168    nqo=nqo_
169    nbtr=nbtr_
170    nqCO2=nqCO2_
171#ifdef CPP_StratAer
172    nbtr_bin=nbtr_bin_
173    nbtr_sulgas=nbtr_sulgas_
174    id_OCS_strat=id_OCS_strat_
175    id_SO2_strat=id_SO2_strat_
176    id_H2SO4_strat=id_H2SO4_strat_
177    id_BIN01_strat=id_BIN01_strat_
178#endif
179    ALLOCATE(tname(nqtot))
180    tname(:) = tname_(:)
181    ALLOCATE(ttext(nqtot))
182    ttext(:) = ttext_(:)
183    type_trac = type_trac_
184    ALLOCATE(niadv(nqtot))
185    niadv(:)=niadv_(:)
186    ALLOCATE(conv_flg(nbtr))
187    conv_flg(:)=conv_flg_(:)
188    ALLOCATE(pbl_flg(nbtr))
189    pbl_flg(:)=pbl_flg_(:)
190    ALLOCATE(solsym(nbtr))
191    solsym(:)=solsym_(:)
192     
193    IF(prt_level.ge.1) THEN
194      write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqCO2",nqtot,nqo,nbtr,nqCO2
195    ENDIF
196   
197    ! Isotopes:
198   
199    ! First check that the "niso_possibles" has the correct value
200    IF (niso_possibles.ne.niso_possibles_) THEN
201      CALL abort_physic(modname,&
202           "wrong value for parameter niso_possibles in infotrac_phy",1)
203    ENDIF
204   
205    ok_isotopes=ok_isotopes_
206    ok_iso_verif=ok_iso_verif_
207    ok_isotrac=ok_isotrac_
208    ok_init_iso=ok_init_iso_
209   
210    niso=niso_
211    ntraceurs_zone=ntraceurs_zone_
212    ntraciso=ntraciso_
213   
214    IF (ok_isotopes) THEN
215      ALLOCATE(nqfils(nqtot))
216      nqfils(:)=nqfils_(:)
217      ALLOCATE(nqdesc(nqtot))
218      nqdesc(:)=nqdesc_(:)
219      nqdesc_tot=nqdesc_tot_
220      ALLOCATE(iqfils(nqtot,nqtot))
221      iqfils(:,:)=iqfils_(:,:)
222      ALLOCATE(iqpere(nqtot))
223      iqpere(:)=iqpere_(:)
224   
225      tnat(:)=tnat_(:)
226      alpha_ideal(:)=alpha_ideal_(:)
227      use_iso(:)=use_iso_(:)
228   
229      ALLOCATE(iqiso(ntraciso,nqo))
230      iqiso(:,:)=iqiso_(:,:)
231      ALLOCATE(iso_num(nqtot))
232      iso_num(:)=iso_num_(:)
233      ALLOCATE(iso_indnum(nqtot))
234      iso_indnum(:)=iso_indnum_(:)
235      ALLOCATE(zone_num(nqtot))
236      zone_num(:)=zone_num_(:)
237      ALLOCATE(phase_num(nqtot))
238      phase_num(:)=phase_num_(:)
239     
240      indnum_fn_num(:)=indnum_fn_num_(:)
241     
242      ALLOCATE(index_trac(ntraceurs_zone,niso))
243      index_trac(:,:)=index_trac_(:,:)
244    ENDIF ! of IF(ok_isotopes)
245 
246  END SUBROUTINE init_infotrac_phy
247
248END MODULE infotrac_phy
Note: See TracBrowser for help on using the repository browser.