source: LMDZ6/trunk/libf/dyn3d_common/infotrac.F90 @ 4056

Last change on this file since 4056 was 4056, checked in by dcugnet, 3 years ago

Most of the changes are intended to help to eventually remove the constraints about the tracers assumptions, in particular water tracers.

  • Remove index tables itr_indice and niadv, replaced by tracers(:)%isAdvected and tracers(:)%isH2OFamily. Most of the loops are now from 1 to nqtot:
    • DO iq=nqo+1,nqtot loops are replaced with: DO iq=1,nqtot

IF(tracers(iq)%isH2Ofamily) CYCLE

  • DO it=1,nbtr; iq=niadv(it+nqo)

and DO it=1,nqtottr; iq=itr_indice(it) loops are replaced with:

it = 0
DO iq = 1, nqtot

IF(.NOT.tracers(iq)%isAdvected .OR. tracers(iq)%isH2Ofamily) CYCLE
it = it+1

  • Move some StratAer? related code from infotrac to infotrac_phy
  • Remove "nqperes" variable:

DO iq=1,nqpere loops are replaced with:
DO iq=1,nqtot

IF(tracers(iq)%parent/='air') CYCLE

  • Cosmetic changes (justification, SELECT CASE instead of multiple IF...) mostly in advtrac* routines.
  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:keywords set to Id
File size: 30.0 KB
Line 
1! $Id: infotrac.F90 4056 2022-01-12 21:54:09Z dcugnet $
2!
3MODULE infotrac
4
5  USE readTracFiles_mod, ONLY: trac_type, isot_type, maxlen, ancestor, delPhase
6
7! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
8  INTEGER, SAVE :: nqtot
9!CR: on ajoute le nombre de traceurs de l eau
10  INTEGER, SAVE :: nqo
11
12! nbtr : number of tracers not including higher order of moment or water vapor or liquid
13!        number of tracers used in the physics
14  INTEGER, SAVE :: nbtr
15
16! Nombre de traceurs passes a phytrac
17  INTEGER, SAVE :: nqtottr
18
19! ThL: nb traceurs CO2
20  INTEGER, SAVE :: nqCO2
21
22! DC: derived types containing informations about tracers and isotopes
23  TYPE(trac_type), TARGET,  SAVE, ALLOCATABLE ::  tracers(:)    !=== TRACERS DESCRIPTORS VECTOR
24  TYPE(isot_type), TARGET,  SAVE, ALLOCATABLE :: isotopes(:)    !=== ISOTOPES PARAMETERS VECTOR
25
26  REAL :: qperemin,masseqmin,ratiomin ! MVals et CRisi
27  PARAMETER (qperemin=1e-30,masseqmin=1e-18,ratiomin=1e-16) ! MVals
28
29! conv_flg(it)=0 : convection desactivated for tracer number it
30  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
31! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
32  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
33
34  CHARACTER(len=4),SAVE :: type_trac
35  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
36
37! CRisi: cas particulier des isotopes
38  LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
39  INTEGER :: niso_possibles   
40  PARAMETER ( niso_possibles=5)
41  REAL, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
42  LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
43  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
44  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numero iso entre 1 et niso effectif en fn de nqtot
45  INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numero d isotope entre 1 et niso_possibles
46  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numero ixt en fn izone, indnum entre 1 et niso
47  INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
48
49CONTAINS
50
51  SUBROUTINE infotrac_init
52    USE control_mod, ONLY: planet_type, config_inca
53#ifdef REPROBUS
54    USE CHEM_REP, ONLY : Init_chem_rep_trac
55#endif
56    IMPLICIT NONE
57!=======================================================================
58!
59!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
60!   -------
61!   Modif special traceur F.Forget 05/94
62!   Modif M-A Filiberti 02/02 lecture de traceur.def
63!
64!   Objet:
65!   ------
66!   GCM LMD nouvelle grille
67!
68!=======================================================================
69!   ... modification de l'integration de q ( 26/04/94 ) ....
70!-----------------------------------------------------------------------
71! Declarations
72
73    INCLUDE "dimensions.h"
74    INCLUDE "iniprint.h"
75
76! Local variables
77    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
78    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
79
80    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca  ! index of horizontal trasport schema
81    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca  ! index of vertical trasport schema
82
83    INTEGER, ALLOCATABLE, DIMENSION(:) :: conv_flg_inca
84    INTEGER, ALLOCATABLE, DIMENSION(:) :: pbl_flg_inca
85    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca
86
87    CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
88    CHARACTER(len=maxlen), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
89    CHARACTER(len=3), DIMENSION(30) :: descrq
90    CHARACTER(len=1), DIMENSION(3)  :: txts
91    CHARACTER(len=2), DIMENSION(9)  :: txtp
92    CHARACTER(len=maxlen)           :: str1,str2
93 
94    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
95    INTEGER :: iq, new_iq, iiq, jq, ierr,itr, iadv
96    INTEGER :: ifils,ipere ! CRisi
97    LOGICAL :: continu,nouveau_traceurdef
98    INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def
99    CHARACTER(len=maxlen) :: tchaine, msg1
100    INTEGER, ALLOCATABLE  :: iqfils(:,:)
101    INTEGER :: nqINCA
102
103    character(len=*),parameter :: modname="infotrac_init"
104
105!-----------------------------------------------------------------------
106! Initialization :
107!
108    txts=(/'x','y','z'/)
109    txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/)
110
111    descrq(14)='VLH'
112    descrq(10)='VL1'
113    descrq(11)='VLP'
114    descrq(12)='FH1'
115    descrq(13)='FH2'
116    descrq(16)='PPM'
117    descrq(17)='PPS'
118    descrq(18)='PPP'
119    descrq(20)='SLP'
120    descrq(30)='PRA'
121   
122    !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
123    WRITE(lunout,*)'type_trac='//TRIM(type_trac)
124    msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
125    SELECT CASE(type_trac)
126      CASE('inca'); WRITE(lunout,*)TRIM(msg1)//' coupling with INCA chemistry model, config_inca='//config_inca
127      CASE('inco'); WRITE(lunout,*)TRIM(msg1)//' coupling jointly with INCA and CO2 cycle'
128      CASE('repr'); WRITE(lunout,*)TRIM(msg1)//' coupling with REPROBUS chemistry model'
129      CASE('co2i'); WRITE(lunout,*)TRIM(msg1)//' you have chosen to run with CO2 cycle'
130      CASE('coag'); WRITE(lunout,*)TRIM(msg1)//' tracers are treated for COAGULATION tests'
131      CASE('lmdz'); WRITE(lunout,*)TRIM(msg1)//' tracers are treated in LMDZ only'
132      CASE DEFAULT
133        CALL abort_gcm(modname,'type_trac='//TRIM(type_trac)//' not possible yet.',1)
134    END SELECT
135
136    !--- COHERENCE TEST BETWEEN "type_trac", "config_inca" AND PREPROCESSING KEYS
137    SELECT CASE(type_trac)
138      CASE('inca','inco'); IF(ALL(['aero', 'aeNP', 'chem']/=config_inca)) &
139        CALL abort_gcm(modname, 'Incoherence between type_trac and config_inca. Please modify "run.def"',1)
140#ifndef INCA
141        CALL abort_gcm(modname, 'You must add cpp key INCA and compile with INCA code',1)
142#endif
143      CASE('repr')
144#ifndef REPROBUS
145        CALL abort_gcm(modname, 'You must add cpp key REPROBUS and compile with REPROBUS code',1)
146#endif
147      CASE('coag')
148#ifndef CPP_StratAer
149        CALL abort_gcm(modname, 'You must add cpp key StratAer and compile with StratAer code',1)
150#endif
151    END SELECT
152
153    !--- Disable "config_inca" option for a run without INCA if it differs from "none"
154    IF (ALL(['inca', 'inco', 'none'] /= config_inca)) THEN
155      WRITE(lunout,*)'setting config_inca="none" as you do not couple with INCA model'
156      config_inca = 'none'
157    END IF
158
159!-----------------------------------------------------------------------
160!
161! 1) Get the true number of tracers + water vapor/liquid
162!    Here true tracers (nqtrue) means declared tracers (only first order)
163!
164!-----------------------------------------------------------------------
165    OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
166    IF(ierr.EQ.0) THEN
167       WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
168    ELSE
169       WRITE(lunout,*) trim(modname),': Failed opening traceur.def'
170       CALL abort_gcm(modname,"file traceur.def not found!",1)
171    ENDIF
172    nqCO2 = 0; IF(type_trac == 'inco') nqCO2 = 1
173    SELECT CASE(type_trac)
174       CASE('lmdz','repr','coag','co2i'); READ(90,*) nqtrue
175       CASE('inca','inco');               READ(90,*) nqo
176          ! The traceur.def file is used to define the number "nqo" of water phases
177          ! present in the simulation. Default : nqo = 2.
178          IF (nqo == 4 .AND. type_trac=='inco') nqo = 3
179          IF(ALL([2,3] /= nqo)) THEN
180             WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowed. Only 2 or 3 water phases allowed'
181             CALL abort_gcm('infotrac_init','Bad number of water phases',1)
182          END IF
183          ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
184#ifdef INCA
185          CALL Init_chem_inca_trac(nqINCA)
186#else
187          nqINCA=0
188#endif
189          nbtr=nqINCA+nqCO2
190          nqtrue=nbtr+nqo
191          WRITE(lunout,*) trim(modname),': nqo    = ',nqo
192          WRITE(lunout,*) trim(modname),': nbtr   = ',nbtr
193          WRITE(lunout,*) trim(modname),': nqtrue = ',nqtrue
194          WRITE(lunout,*) trim(modname),': nqCO2 = ',nqCO2
195          WRITE(lunout,*) trim(modname),': nqINCA = ',nqINCA
196          ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA), conv_flg_inca(nqINCA), pbl_flg_inca(nqINCA), solsym_inca(nqINCA))
197    END SELECT
198!>jyg
199
200    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
201       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowed. 2 tracers is the minimum'
202       CALL abort_gcm('infotrac_init','Not enough tracers',1)
203    ENDIF
204   
205!jyg<
206       
207!
208! Allocate variables depending on nqtrue
209!
210    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue),tnom_transp(nqtrue))
211
212
213!-----------------------------------------------------------------------
214! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
215!
216!     iadv = 1    schema  transport type "humidite specifique LMD"
217!     iadv = 2    schema   amont
218!     iadv = 14   schema  Van-leer + humidite specifique
219!                            Modif F.Codron
220!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
221!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
222!     iadv = 12   schema  Frederic Hourdin I
223!     iadv = 13   schema  Frederic Hourdin II
224!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
225!     iadv = 17   schema  PPM Semi Monotone (overshoots autorises)
226!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorises)
227!     iadv = 20   schema  Slopes
228!     iadv = 30   schema  Prather
229!
230!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
231!                                     iq = 2  pour l'eau liquide
232!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
233!
234!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
235!------------------------------------------------------------------------
236!
237!    Get choice of advection schema from file tracer.def or from INCA
238!---------------------------------------------------------------------
239    IF (ANY(['lmdz', 'repr', 'coag', 'co2i'] == type_trac)) THEN
240
241       ! Continue to read tracer.def
242       DO iq=1,nqtrue
243
244          write(*,*) 'infotrac 237: iq=',iq
245          ! CRisi: ajout du nom du fluide transporteur
246          ! mais rester retro compatible
247          READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
248          write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
249          write(lunout,*) 'tchaine=',trim(tchaine)
250          write(*,*) 'infotrac 238: IOstatus=',IOstatus
251          if (IOstatus.ne.0) CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
252          ! Y-a-t-il 1 ou 2 noms de traceurs separes par un espace ?
253          iiq = INDEX(tchaine(1:LEN_TRIM(tchaine)),' ')
254          nouveau_traceurdef=iiq/=0
255          write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
256          if (nouveau_traceurdef) then
257             IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def"
258             tnom_0     (iq) = tchaine(1:iiq-1)
259             tnom_transp(iq) = tchaine(iiq+1:)
260          else
261             IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def: traceurs d'air uniquement"
262             tnom_0     (iq) = tchaine
263             tnom_transp(iq) = 'air'
264          endif
265          write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
266          write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
267       ENDDO!DO iq=1,nqtrue
268
269       CLOSE(90) 
270
271       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
272       WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue
273       DO iq=1,nqtrue
274          WRITE(lunout,*) hadv(iq),vadv(iq),' ',trim(tnom_0(iq)),' ',trim(tnom_transp(iq))
275       END DO
276
277       IF ( planet_type=='earth') THEN
278         !CR: nombre de traceurs de l eau
279         nqo=2; IF (tnom_0(3) == 'H2Oi') nqo=3
280         ! For Earth, water vapour & liquid tracers are not in the physics
281         nbtr=nqtrue-nqo
282       ELSE
283         ! Other planets (for now); we have the same number of tracers
284         ! in the dynamics than in the physics
285         nbtr=nqtrue
286       ENDIF
287
288    ENDIF
289!jyg<
290!
291
292! Transfert number of tracers to Reprobus
293#ifdef REPROBUS
294    IF (type_trac == 'repr') CALL Init_chem_rep_trac(nbtr,nqo,tnom_0)
295#endif
296!
297! Allocate variables depending on nbtr
298!
299    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
300    conv_flg(:) = 1 ! convection activated for all tracers
301    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
302
303    IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN   ! config_inca='aero' ou 'chem'
304!>jyg
305! le module de chimie fournit les noms des traceurs et les schemas d'advection associes.
306! excepte pour ceux lus dans traceur.def
307
308#ifdef INCA
309       CALL init_transport(hadv_inca, vadv_inca, conv_flg_inca, pbl_flg_inca, solsym_inca)
310       ! DC passive CO2 tracer is at index 1: H2O was removed ; nqCO2/=0 in "inco" case only
311       conv_flg(1:nqCO2) = 1;   conv_flg(1+nqCO2:nbtr) = conv_flg_inca
312        pbl_flg(1:nqCO2) = 1;    pbl_flg(1+nqCO2:nbtr) =  pbl_flg_inca
313         solsym(1:nqCO2) = 'CO2'; solsym(1+nqCO2:nbtr) =   solsym_inca
314#endif
315
316       itr = 0
317       DO iq = 1, nqtot
318          IF(iq > nqo+nqCO2) THEN
319             itr = itr+1
320             hadv  (iq) = hadv_inca  (itr)
321             vadv  (iq) = vadv_inca  (itr)
322             tnom_0(iq) = solsym_inca(itr)
323             tnom_transp(iq) = 'air'
324             CYCLE
325          END IF
326          write(*,*) 'infotrac 237: iq=',iq
327          ! CRisi: ajout du nom du fluide transporteur en restant retro-compatible
328          READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
329          write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
330          write(lunout,*) 'tchaine=',trim(tchaine)
331          write(*,*) 'infotrac 238: IOstatus=',IOstatus
332          if (IOstatus.ne.0) CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
333          ! Y-a-t-il 1 ou 2 noms de traceurs separes par un espace ?
334          iiq = INDEX(tchaine(1:LEN_TRIM(tchaine)),' ')
335          nouveau_traceurdef=iiq/=0
336          write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
337          if (nouveau_traceurdef) then
338             IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def"
339             tnom_0     (iq) = tchaine(1:iiq-1)
340             tnom_transp(iq) = tchaine(iiq+1:)
341          else
342             IF(iq==1) write(lunout,*) "Nouvelle version de traceur.def: traceurs d'air uniquement"
343             tnom_0     (iq) = tchaine
344             tnom_transp(iq) = 'air'
345          endif
346          write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
347          write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
348       END DO
349       CLOSE(90) 
350    ENDIF ! (type_trac == 'inca' or 'inco')
351
352!-----------------------------------------------------------------------
353!
354! 3) Verify if advection schema 20 or 30 choosen
355!    Calculate total number of tracers needed: nqtot
356!    Allocate variables depending on total number of tracers
357!-----------------------------------------------------------------------
358    new_iq=0
359    DO iq=1,nqtrue
360       ! Add tracers for certain advection schema
361       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
362          new_iq=new_iq+1  ! no tracers added
363       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
364          new_iq=new_iq+4  ! 3 tracers added
365       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
366          new_iq=new_iq+10 ! 9 tracers added
367       ELSE
368          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
369          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
370       ENDIF
371    END DO
372   
373    IF (new_iq /= nqtrue) THEN
374       ! The choice of advection schema imposes more tracers
375       ! Assigne total number of tracers
376       nqtot = new_iq
377
378       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
379       WRITE(lunout,*) 'makes it necessary to add tracers'
380       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
381       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
382
383    ELSE
384       ! The true number of tracers is also the total number
385       nqtot = nqtrue
386    ENDIF
387
388!
389! Allocate variables with total number of tracers, nqtot
390!
391    ALLOCATE(tracers(nqtot))
392
393!-----------------------------------------------------------------------
394!
395! 4) Determine iadv, long and short name
396!
397!-----------------------------------------------------------------------
398    new_iq=0
399    DO iq=1,nqtrue
400       new_iq=new_iq+1
401
402       ! Verify choice of advection schema
403       IF (hadv(iq)==vadv(iq)) THEN
404          tracers(new_iq)%iadv=hadv(iq)
405       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
406          tracers(new_iq)%iadv=11
407       ELSE
408          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
409
410          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
411       ENDIF
412     
413       str1=tnom_0(iq)
414       tracers(new_iq)%name = TRIM(tnom_0(iq))
415       tracers(new_iq)%parent = TRIM(tnom_transp(iq))
416       IF (tracers(new_iq)%iadv==0) THEN
417          tracers(new_iq)%longName=trim(str1)
418       ELSE
419          tracers(new_iq)%longName=trim(tnom_0(iq))//descrq(tracers(new_iq)%iadv)
420       ENDIF
421
422       ! schemas tenant compte des moments d'ordre superieur
423       str2=TRIM(tracers(new_iq)%longName)
424       IF (tracers(new_iq)%iadv==20) THEN
425          DO jq=1,3
426             new_iq=new_iq+1
427             tracers(new_iq)%iadv=-20
428             tracers(new_iq)%longName=trim(str2)//txts(jq)
429             tracers(new_iq)%name=trim(str1)//txts(jq)
430          END DO
431       ELSE IF (tracers(new_iq)%iadv==30) THEN
432          DO jq=1,9
433             new_iq=new_iq+1
434             tracers(new_iq)%iadv=-30
435             tracers(new_iq)%longName=trim(str2)//txtp(jq)
436             tracers(new_iq)%name=trim(str1)//txtp(jq)
437          END DO
438       ENDIF
439    END DO
440
441    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
442    WRITE(lunout,*) trim(modname),': iadv  name  long_name :'
443
444    DO iq=1,nqtot
445       WRITE(lunout,*) tracers(iq)%iadv,' ',trim(tracers(iq)%name),' ',trim(tracers(iq)%longName)
446    END DO
447
448!
449! Test for advection schema.
450! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
451!
452    DO iq=1,nqtot
453       iadv=tracers(iq)%iadv
454       IF (ALL([10, 14, 0]/=iadv)) THEN
455          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not tested in this version of LMDZ'
456          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
457       ELSE IF (iadv==14 .AND. iq/=1) THEN
458          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv,' is not tested in this version of LMDZ'
459          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
460       ENDIF
461    END DO
462
463
464! CRisi: quels sont les traceurs fils et les traceurs peres.
465! initialiser tous les tableaux d'indices lies aux traceurs familiaux
466! + verifier que tous les peres sont ecrits en premieres positions
467    ALLOCATE(iqfils(nqtot,nqtot))   
468    iqfils(:,:)=0
469    tracers(:)%iqParent=0
470    DO iq=1,nqtot
471      if (tnom_transp(iq) == 'air') then
472        ! ceci est un traceur pere
473        WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un pere'
474        tracers(iq)%iqParent=0
475      else !if (tnom_transp(iq) == 'air') then
476        ! ceci est un fils. Qui est son pere?
477        WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un fils'
478        continu=.true.
479        ipere=1
480        do while (continu)           
481          if (tnom_transp(iq) == tnom_0(ipere)) then
482            ! Son pere est ipere
483            WRITE(lunout,*) 'Le traceur',iq,'appele ', &
484      &          trim(tnom_0(iq)),' est le fils de ',ipere,'appele ',trim(tnom_0(ipere))
485            if (iq.eq.ipere) then
486                CALL abort_gcm('infotrac_init','Un fils est son propre pere',1)
487            endif
488            tracers(ipere)%nqChilds = tracers(ipere)%nqChilds+1 
489            iqfils(tracers(ipere)%nqChilds,ipere)=iq
490            tracers(iq)%iqParent=ipere         
491            continu=.false.
492          else !if (tnom_transp(iq) == tnom_0(ipere)) then
493            ipere=ipere+1
494            if (ipere.gt.nqtot) then
495                WRITE(lunout,*) 'Le traceur',iq,'appele ', &
496      &          trim(tnom_0(iq)),', est orphelin.'
497                CALL abort_gcm('infotrac_init','Un traceur est orphelin',1)
498            endif !if (ipere.gt.nqtot) then
499          endif !if (tnom_transp(iq) == tnom_0(ipere)) then
500        enddo !do while (continu)
501      endif !if (tnom_transp(iq) == 'air') then
502    enddo !DO iq=1,nqtot
503    WRITE(lunout,*) 'infotrac: nqGen0=',COUNT(tracers(:)%parent == 'air')
504    WRITE(lunout,*) 'nqChilds=',tracers(:)%nqChilds
505    WRITE(lunout,*) 'iqParent=',tracers(:)%iqParent
506    WRITE(lunout,*) 'iqfils=',iqfils
507
508! Calculer le nombre de descendants a partir de iqfils et de nbfils
509    DO iq=1,nqtot   
510      tracers(iq)%iGeneration=0
511      continu=.true.
512      ifils=iq
513      do while (continu)
514        ipere=tracers(ifils)%iqParent
515        if (ipere.gt.0) then
516         tracers(ipere)%nqDescen = tracers(ipere)%nqDescen+1   
517         iqfils(tracers(ipere)%nqDescen,ipere)=iq
518         ifils=ipere
519         tracers(iq)%iGeneration=tracers(iq)%iGeneration+1
520        else !if (ipere.gt.0) then
521         continu=.false.
522        endif !if (ipere.gt.0) then
523      enddo !do while (continu)   
524      WRITE(lunout,*) 'Le traceur ',iq,', appele ',trim(tnom_0(iq)), &
525        ' est un traceur de generation: ',tracers(iq)%iGeneration
526    enddo !DO iq=1,nqtot
527    DO iq=1,nqtot
528      ALLOCATE(tracers(iq)%iqDescen(tracers(iq)%nqDescen))
529      tracers(iq)%iqDescen(:) = iqfils(1:tracers(iq)%nqDescen,iq)
530    END DO
531
532    WRITE(lunout,*) 'infotrac: nqDescen=',tracers(:)%nqDescen
533    WRITE(lunout,*) 'iqfils=',iqfils
534    WRITE(lunout,*) 'nqDescen_tot=',SUM(tracers(:)%nqDescen)
535
536! Interdire autres schemas que 10 pour les traceurs fils, et autres schemas
537! que 10 et 14 si des peres ont des fils
538    do iq=1,nqtot
539      if (tracers(iq)%iqParent > 0) then
540        ! ce traceur a un pere qui n'est pas l'air
541        ! Seul le schema 10 est autorise
542        iadv=tracers(iq)%iadv
543        if (iadv/=10) then
544           WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not implemented for sons'
545          CALL abort_gcm('infotrac_init','Sons should be advected by scheme 10',1)
546        endif
547        ! Le traceur pere ne peut etre advecte que par schema 10 ou 14:
548        IF (ALL([10,14]/=tracers(tracers(iq)%iqParent)%iadv)) THEN
549          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv,' is not implemented for fathers'
550          CALL abort_gcm('infotrac_init','Fathers should be advected by scheme 10 ou 14',1)
551        endif
552     endif
553    enddo !do iq=1,nqtot
554    tracers(:)%gen0Name = ancestor(tracers)      !--- Name of the first generation ancestor
555    tracers(:)%isAdvected = tracers(:)%iadv  >   0
556!    tracers(:)%isH2Ofamily = delPhase(tracers(:)%gen0Name) == 'H2O'
557    tracers(:)%isH2Ofamily = [(tracers(iq)%gen0Name(1:3) == 'H2O', iq=1, nqtot)]
558
559! detecter quels sont les traceurs isotopiques parmi des traceurs
560    call infotrac_isoinit(tnom_0,nqtrue)
561
562!    if (ntraciso.gt.0) then
563! le 18 sep 2020: on enleve la condition ntraciso.gt.0 car nqtottr doit etre
564! connu meme si il n'y a pas d'isotopes!
565        write(lunout,*) 'infotrac 702: nbtr,ntraciso=',nbtr,ntraciso
566! retrancher les traceurs isotopiques de la liste des traceurs qui passent dans
567! phytrac
568        nbtr=nbtr-nqo*ntraciso
569
570! faire un tableau d'indice des traceurs qui passeront dans phytrac
571        nqtottr=nqtot-nqo*(1+ntraciso)
572        write(lunout,*) 'infotrac 704: nqtottr,nqtot,nqo=',nqtottr,nqtot,nqo
573        ! Rq: nqtottr n'est pas forcement egal a nbtr dans le cas ou new_iq /= nqtrue
574        if (COUNT(tracers(:)%iso_iName == 0) /= nqtottr) &
575            CALL abort_gcm('infotrac_init','pb dans le calcul de nqtottr',1)
576!    endif !if (ntraciso.gt.0) then
577
578!-----------------------------------------------------------------------
579! Finalize :
580!
581    DEALLOCATE(tnom_0, hadv, vadv,tnom_transp)
582
583    WRITE(lunout,*) 'infotrac init fin'
584
585  END SUBROUTINE infotrac_init
586
587  SUBROUTINE infotrac_isoinit(tnom_0,nqtrue)
588
589#ifdef CPP_IOIPSL
590  use IOIPSL
591#else
592  ! if not using IOIPSL, we still need to use (a local version of) getin
593  use ioipsl_getincom
594#endif
595  implicit none
596 
597    ! inputs
598    INTEGER,INTENT(IN) :: nqtrue
599    CHARACTER(len=*),INTENT(IN) :: tnom_0(nqtrue)
600   
601    ! locals   
602    CHARACTER(len=3), DIMENSION(niso_possibles) :: tnom_iso
603    INTEGER, ALLOCATABLE,DIMENSION(:,:) :: nb_iso,nb_traciso
604    INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind
605    INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone
606    CHARACTER(len=maxlen) :: tnom_trac
607    INCLUDE "iniprint.h"
608
609    tnom_iso=(/'eau','HDO','O18','O17','HTO'/)
610
611    ALLOCATE(nb_iso(niso_possibles,nqo))
612    ALLOCATE(nb_isoind(nqo))
613    ALLOCATE(nb_traciso(niso_possibles,nqo))
614    ALLOCATE(iso_indnum(nqtot))
615     
616    iso_indnum(:)=0
617    indnum_fn_num(:)=0
618    use_iso(:)=.false. 
619    nb_iso(:,:)=0 
620    nb_isoind(:)=0     
621    nb_traciso(:,:)=0
622    niso=0
623    ntraceurs_zone=0 
624    ntraceurs_zone_prec=0
625    ntraciso=0
626
627    do iq=nqo+1,nqtot
628!       write(lunout,*) 'infotrac 569: iq,tnom_0(iq)=',iq,tnom_0(iq)
629       do phase=1,nqo   
630        do ixt= 1,niso_possibles   
631         tnom_trac=trim(tnom_0(phase))//'_'
632         tnom_trac=trim(tnom_trac)//trim(tnom_iso(ixt))
633!         write(*,*) 'phase,ixt,tnom_trac=',phase,ixt,tnom_trac     
634         IF (tnom_0(iq) == tnom_trac) then
635!          write(lunout,*) 'Ce traceur est un isotope'
636          nb_iso(ixt,phase)=nb_iso(ixt,phase)+1   
637          nb_isoind(phase)=nb_isoind(phase)+1   
638          tracers(iq)%iso_iName=ixt
639          iso_indnum(iq)=nb_isoind(phase)
640          indnum_fn_num(ixt)=iso_indnum(iq)
641          tracers(iq)%iso_iPhase=phase
642          goto 20
643         else if ( tracers(iq)%iqParent> 0) then         
644          if (tnom_0(tracers(iq)%iqParent) == tnom_trac) then
645!           write(lunout,*) 'Ce traceur est le fils d''un isotope'
646           ! c'est un traceur d'isotope
647           nb_traciso(ixt,phase)=nb_traciso(ixt,phase)+1
648           tracers(iq)%iso_iName=ixt
649           iso_indnum(iq)=indnum_fn_num(ixt)
650           tracers(iq)%iso_iZone=nb_traciso(ixt,phase)
651           tracers(iq)%iso_iPhase=phase
652           goto 20
653          endif !if (tnom_0(tracers(iq)%iqParent) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
654         endif !IF (tnom_0(iq) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
655        enddo !do ixt= niso_possibles
656       enddo !do phase=1,nqo
657  20   continue
658      enddo !do iq=1,nqtot
659
660      do ixt= 1,niso_possibles 
661
662        if (nb_iso(ixt,1).eq.1) then
663          ! on verifie que toutes les phases ont le meme nombre de
664          ! traceurs
665          do phase=2,nqo
666            if (nb_iso(ixt,phase).ne.nb_iso(ixt,1)) then
667!              write(lunout,*) 'ixt,phase,nb_iso=',ixt,phase,nb_iso(ixt,phase)
668              CALL abort_gcm('infotrac_init','Phases must have same number of isotopes',1)
669            endif
670          enddo !do phase=2,nqo
671
672          niso=niso+1
673          use_iso(ixt)=.true.
674          ntraceurs_zone=nb_traciso(ixt,1)
675
676          ! on verifie que toutes les phases ont le meme nombre de
677          ! traceurs
678          do phase=2,nqo
679            if (nb_traciso(ixt,phase).ne.ntraceurs_zone) then
680              write(lunout,*) 'ixt,phase,nb_traciso=',ixt,phase,nb_traciso(ixt,phase)
681              write(lunout,*) 'ntraceurs_zone=',ntraceurs_zone
682              CALL abort_gcm('infotrac_init','Phases must have same number of tracers',1)
683            endif 
684          enddo  !do phase=2,nqo
685          ! on verifie que tous les isotopes ont le meme nombre de
686          ! traceurs
687          if (ntraceurs_zone_prec.gt.0) then               
688            if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
689              ntraceurs_zone_prec=ntraceurs_zone
690            else !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
691              write(*,*) 'ntraceurs_zone_prec,ntraceurs_zone=',ntraceurs_zone_prec,ntraceurs_zone   
692              CALL abort_gcm('infotrac_init', &
693               &'Isotope tracers are not well defined in traceur.def',1)           
694            endif !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
695           endif !if (ntraceurs_zone_prec.gt.0) then
696
697        else if (nb_iso(ixt,1).ne.0) then
698           WRITE(lunout,*) 'nqo,ixt=',nqo,ixt
699           WRITE(lunout,*) 'nb_iso(ixt,1)=',nb_iso(ixt,1)   
700           CALL abort_gcm('infotrac_init','Isotopes are not well defined in traceur.def',1)     
701        endif   !if (nb_iso(ixt,1).eq.1) then       
702    enddo ! do ixt= niso_possibles
703
704    ! dimensions isotopique:
705    ntraciso=niso*(ntraceurs_zone+1)
706!    WRITE(lunout,*) 'niso=',niso
707!    WRITE(lunout,*) 'ntraceurs_zone,ntraciso=',ntraceurs_zone,ntraciso   
708 
709    ! flags isotopiques:
710    ok_isotopes = niso > 0
711!    WRITE(lunout,*) 'ok_isotopes=',ok_isotopes
712 
713    if (ok_isotopes) then
714        ok_iso_verif=.false.
715        call getin('ok_iso_verif',ok_iso_verif)
716        ok_init_iso=.false.
717        call getin('ok_init_iso',ok_init_iso)
718        tnat=(/1.0,155.76e-6,2005.2e-6,0.004/100.,0.0/)
719        alpha_ideal=(/1.0,1.01,1.006,1.003,1.0/)
720    endif !if (ok_isotopes) then 
721!    WRITE(lunout,*) 'ok_iso_verif=',ok_iso_verif
722!    WRITE(lunout,*) 'ok_init_iso=',ok_init_iso
723
724    if (ntraceurs_zone.gt.0) then
725        ok_isotrac=.true.
726    else
727        ok_isotrac=.false.
728    endif   
729!    WRITE(lunout,*) 'ok_isotrac=',ok_isotrac
730
731    ! remplissage du tableau iqiso(ntraciso,phase)
732    ALLOCATE(iqiso(ntraciso,nqo))   
733    iqiso(:,:)=0     
734    do iq=1,nqtot
735        if (tracers(iq)%iso_iName > 0) then
736          ixt=iso_indnum(iq)+tracers(iq)%iso_iZone*niso
737          iqiso(ixt,tracers(iq)%iso_iPhase)=iq
738        endif
739    enddo
740!    WRITE(lunout,*) 'iqiso=',iqiso
741
742    ! replissage du tableau index_trac(ntraceurs_zone,niso)
743    ALLOCATE(index_trac(ntraceurs_zone,niso)) 
744    if (ok_isotrac) then
745        do iiso=1,niso
746          do izone=1,ntraceurs_zone
747             index_trac(izone,iiso)=iiso+izone*niso
748          enddo
749        enddo
750    else !if (ok_isotrac) then     
751        index_trac(:,:)=0.0
752    endif !if (ok_isotrac) then
753!    write(lunout,*) 'index_trac=',index_trac   
754
755! Finalize :
756    DEALLOCATE(nb_iso)
757
758  END SUBROUTINE infotrac_isoinit
759
760END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.