source: LMDZ6/trunk/libf/phylmdiso/infotrac_phy.F90 @ 3940

Last change on this file since 3940 was 3940, checked in by crisi, 3 years ago

replace files by symbloic liks from phylmdiso towards phylmd.
Many files at once

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