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

Last change on this file since 3927 was 3927, checked in by Laurent Fairhead, 3 years ago

Initial import of the physics wih isotopes from Camille Risi
CR

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