LMDZ
infotrac_phy.F90
Go to the documentation of this file.
1 
2 ! $Id: $
3 
4 MODULE 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 ! CRisi: nb traceurs pères= directement advectés par l'air
24  INTEGER, SAVE :: nqperes
25 
26 ! Name variables
27  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
28  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
29 !$OMP THREADPRIVATE(tname,ttext)
30 
31 !! iadv : index of trasport schema for each tracer
32 ! INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iadv
33 
34 ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
35 ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
36  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique
37 !$OMP THREADPRIVATE(niadv)
38 
39 ! CRisi: tableaux de fils
40  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqfils
41  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
42  INTEGER, SAVE :: nqdesc_tot
43  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqfils
44  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iqpere
45 !$OMP THREADPRIVATE(nqfils,nqdesc,nqdesc_tot,iqfils,iqpers)
46 
47 ! conv_flg(it)=0 : convection desactivated for tracer number it
48  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg
49 !$OMP THREADPRIVATE(conv_flg)
50 
51 ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it
52  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg
53 !$OMP THREADPRIVATE(pbl_flg)
54 
55  CHARACTER(len=4),SAVE :: type_trac
56 !$OMP THREADPRIVATE(type_trac)
57  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
58 !$OMP THREADPRIVATE(solsym)
59 
60  ! CRisi: cas particulier des isotopes
62 !$OMP THREADPRIVATE(ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso)
63  INTEGER :: niso_possibles
65  real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
66 !$OMP THREADPRIVATE(tnat,alpha_ideal)
67  LOGICAL, DIMENSION(niso_possibles),SAVE :: use_iso
68 !$OMP THREADPRIVATE(use_iso)
69  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqiso ! donne indice iq en fn de (ixt,phase)
70 !$OMP THREADPRIVATE(iqiso)
71  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
72 !$OMP THREADPRIVATE(iso_num)
73  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
74 !$OMP THREADPRIVATE(iso_indnum)
75  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: zone_num ! donne numéro de la zone de tracage en fn de nqtot
76 !$OMP THREADPRIVATE(zone_num)
77  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: phase_num ! donne numéro de la zone de tracage en fn de nqtot
78 !$OMP THREADPRIVATE(phase_num)
79  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
80 !$OMP THREADPRIVATE(indnum_fn_num)
81  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
82 !$OMP THREADPRIVATE(index_trac)
83  INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
84 !$OMP THREADPRIVATE(niso,ntraceurs_zone,ntraciso)
85 
86 CONTAINS
87 
88  SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,tname_,ttext_,type_trac_,&
89  niadv_,conv_flg_,pbl_flg_,solsym_,&
90  nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
91  ok_isotopes_,ok_iso_verif_,ok_isotrac_,&
92  ok_init_iso_,niso_possibles_,tnat_,&
93  alpha_ideal_,use_iso_,iqiso_,iso_num_,&
94  iso_indnum_,zone_num_,phase_num_,&
95  indnum_fn_num_,index_trac_,&
96  niso_,ntraceurs_zone_,ntraciso_)
97  ! transfer information on tracers from dynamics to physics
99  IMPLICIT NONE
100  INTEGER,INTENT(IN) :: nqtot_
101  INTEGER,INTENT(IN) :: nqo_
102  INTEGER,INTENT(IN) :: nbtr_
103  CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
104  CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
105  CHARACTER(len=4),INTENT(IN) :: type_trac_
106  INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
107  INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
108  INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)
109  CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)
110  ! Isotopes:
111  INTEGER,INTENT(IN) :: nqfils_(nqtot_)
112  INTEGER,INTENT(IN) :: nqdesc_(nqtot_)
113  INTEGER,INTENT(IN) :: nqdesc_tot_
114  INTEGER,INTENT(IN) :: iqfils_(nqtot_,nqtot_)
115  INTEGER,INTENT(IN) :: iqpere_(nqtot_)
116  LOGICAL,INTENT(IN) :: ok_isotopes_
117  LOGICAL,INTENT(IN) :: ok_iso_verif_
118  LOGICAL,INTENT(IN) :: ok_isotrac_
119  LOGICAL,INTENT(IN) :: ok_init_iso_
120  INTEGER,INTENT(IN) :: niso_possibles_
121  REAL,INTENT(IN) :: tnat_(niso_possibles_)
122  REAL,INTENT(IN) :: alpha_ideal_(niso_possibles_)
123  LOGICAL,INTENT(IN) :: use_iso_(niso_possibles_)
124  INTEGER,INTENT(IN) :: iqiso_(ntraciso_,nqo_)
125  INTEGER,INTENT(IN) :: iso_num_(nqtot_)
126  INTEGER,INTENT(IN) :: iso_indnum_(nqtot_)
127  INTEGER,INTENT(IN) :: zone_num_(nqtot_)
128  INTEGER,INTENT(IN) :: phase_num_(nqtot_)
129  INTEGER,INTENT(IN) :: indnum_fn_num_(niso_possibles_)
130  INTEGER,INTENT(IN) :: index_trac_(ntraceurs_zone_,niso_)
131  INTEGER,INTENT(IN) :: niso_
132  INTEGER,INTENT(IN) :: ntraceurs_zone_
133  INTEGER,INTENT(IN) :: ntraciso_
134 
135  CHARACTER(LEN=30) :: modname="init_infotrac_phy"
136 
137  nqtot=nqtot_
138  nqo=nqo_
139  nbtr=nbtr_
140  ALLOCATE(tname(nqtot))
141  tname(:) = tname_(:)
142  ALLOCATE(ttext(nqtot))
143  ttext(:) = ttext_(:)
144  type_trac = type_trac_
145  ALLOCATE(niadv(nqtot))
146  niadv(:)=niadv_(:)
147  ALLOCATE(conv_flg(nbtr))
148  conv_flg(:)=conv_flg_(:)
149  ALLOCATE(pbl_flg(nbtr))
150  pbl_flg(:)=pbl_flg_(:)
151  ALLOCATE(solsym(nbtr))
152  solsym(:)=solsym_(:)
153 
154  IF(prt_level.ge.1) THEN
155  write(lunout,*) trim(modname)//": nqtot,nqo,nbtr",nqtot,nqo,nbtr
156  ENDIF
157 
158  ! Isotopes:
159 
160  ! First check that the "niso_possibles" has the correct value
161  IF (niso_possibles.ne.niso_possibles_) THEN
162  CALL abort_physic(modname,&
163  "wrong value for parameter niso_possibles in infotrac_phy",1)
164  ENDIF
165 
166  ok_isotopes=ok_isotopes_
167  ok_iso_verif=ok_iso_verif_
168  ok_isotrac=ok_isotrac_
169  ok_init_iso=ok_init_iso_
170 
171  niso=niso_
172  ntraceurs_zone=ntraceurs_zone_
173  ntraciso=ntraciso_
174 
175  IF (ok_isotopes) THEN
176  ALLOCATE(nqfils(nqtot))
177  nqfils(:)=nqfils_(:)
178  ALLOCATE(nqdesc(nqtot))
179  nqdesc(:)=nqdesc_(:)
180  nqdesc_tot=nqdesc_tot_
181  ALLOCATE(iqfils(nqtot,nqtot))
182  iqfils(:,:)=iqfils_(:,:)
183  ALLOCATE(iqpere(nqtot))
184  iqpere(:)=iqpere_(:)
185 
186  tnat(:)=tnat_(:)
187  alpha_ideal(:)=alpha_ideal_(:)
188  use_iso(:)=use_iso_(:)
189 
190  ALLOCATE(iqiso(ntraciso,nqo))
191  iqiso(:,:)=iqiso_(:,:)
192  ALLOCATE(iso_num(nqtot))
193  iso_num(:)=iso_num_(:)
194  ALLOCATE(iso_indnum(nqtot))
195  iso_indnum(:)=iso_indnum_(:)
196  ALLOCATE(zone_num(nqtot))
197  zone_num(:)=zone_num_(:)
198  ALLOCATE(phase_num(nqtot))
199  phase_num(:)=phase_num_(:)
200 
201  indnum_fn_num(:)=indnum_fn_num_(:)
202 
203  ALLOCATE(index_trac(ntraceurs_zone,niso))
204  index_trac(:,:)=index_trac_(:,:)
205  ENDIF ! of IF(ok_isotopes)
206 
207  END SUBROUTINE init_infotrac_phy
208 
209 END MODULE infotrac_phy
character(len=8), dimension(:), allocatable, save solsym
integer, dimension(:), allocatable, save phase_num
integer, dimension(niso_possibles), save indnum_fn_num
integer, dimension(:), allocatable, save nqfils
integer, save nbtr
integer, dimension(:,:), allocatable, save index_trac
integer, save nqdesc_tot
integer, save ntraciso
integer niso_possibles
logical, save ok_isotrac
real, dimension(niso_possibles), save alpha_ideal
real, dimension(niso_possibles), save tnat
integer, save nqperes
integer, dimension(:), allocatable, save conv_flg
integer, dimension(:), allocatable, save pbl_flg
integer, dimension(:), allocatable, save niadv
integer, dimension(:), allocatable, save nqdesc
integer, dimension(:), allocatable, save iso_indnum
integer, save nqtot
Definition: infotrac_phy.F90:8
integer, dimension(:), allocatable, save iqpere
integer, dimension(:), allocatable, save zone_num
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx
character(len=23), dimension(:), allocatable, save ttext
integer, dimension(:,:), allocatable, save iqfils
logical, save ok_isotopes
character(len=20), dimension(:), allocatable, save tname
integer, save niso
logical, dimension(niso_possibles), save use_iso
character(len=4), save type_trac
subroutine abort_physic(modname, message, ierr)
Definition: abort_physic.F90:3
integer, save ntraceurs_zone
subroutine init_infotrac_phy(nqtot_, type_trac_)
logical, save ok_init_iso
integer, dimension(:,:), allocatable, save iqiso
integer, save nqo
integer, dimension(:), allocatable, save iso_num
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
logical, save ok_iso_verif