source: LMDZ5/branches/IPSLCM5A2.1_ISO/libf/dyn3d_common/infotrac.F90 @ 3822

Last change on this file since 3822 was 3331, checked in by acozic, 6 years ago

Add modification for isotopes

  • 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
File size: 34.9 KB
Line 
1! $Id$
2!
3MODULE infotrac
4
5! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
6  INTEGER, SAVE :: nqtot
7!CR: on ajoute le nombre de traceurs de l eau
8  INTEGER, SAVE :: nqo
9
10! nbtr : number of tracers not including higher order of moment or water vapor or liquid
11!        number of tracers used in the physics
12  INTEGER, SAVE :: nbtr
13
14! CRisi: on retranche les isotopes des traceurs habituels
15! On fait un tableaux d'indices des traceurs qui passeront dans phytrac
16  INTEGER, SAVE :: nqtottr
17  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: itr_indice
18
19! CRisi: nb traceurs pères= directement advectés par l'air
20  INTEGER, SAVE :: nqperes
21
22! Name variables
23  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
24  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
25
26! iadv  : index of trasport schema for each tracer
27  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
28
29! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
30!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
31  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
32
33! CRisi: tableaux de fils
34  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqfils
35  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
36  INTEGER, SAVE :: nqdesc_tot
37  INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE    :: iqfils
38  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iqpere
39
40! conv_flg(it)=0 : convection desactivated for tracer number it
41  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
42! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
43  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
44
45  CHARACTER(len=4),SAVE :: type_trac
46  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
47   
48    ! CRisi: cas particulier des isotopes
49    LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
50    INTEGER :: niso_possibles   
51    PARAMETER ( niso_possibles=5)
52    real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
53    LOGICAL, DIMENSION(niso_possibles),SAVE ::  use_iso
54    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  iqiso ! donne indice iq en fn de (ixt,phase)
55    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
56    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
57    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  zone_num ! donne numéro de la zone de tracage en fn de nqtot
58    INTEGER, ALLOCATABLE, DIMENSION(:), SAVE ::  phase_num ! donne numéro de la zone de tracage en fn de nqtot
59    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
60    INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE ::  index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
61    INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
62 
63CONTAINS
64
65  SUBROUTINE infotrac_init
66    USE control_mod, ONLY: planet_type, config_inca
67#ifdef REPROBUS
68    USE CHEM_REP, ONLY : Init_chem_rep_trac
69#endif
70    IMPLICIT NONE
71!=======================================================================
72!
73!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
74!   -------
75!   Modif special traceur F.Forget 05/94
76!   Modif M-A Filiberti 02/02 lecture de traceur.def
77!
78!   Objet:
79!   ------
80!   GCM LMD nouvelle grille
81!
82!=======================================================================
83!   ... modification de l'integration de q ( 26/04/94 ) ....
84!-----------------------------------------------------------------------
85! Declarations
86
87    INCLUDE "dimensions.h"
88    INCLUDE "iniprint.h"
89
90! Local variables
91    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
92    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
93
94    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca  ! index of horizontal trasport schema
95    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca  ! index of vertical trasport schema
96
97    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
98    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
99    CHARACTER(len=3), DIMENSION(30) :: descrq
100    CHARACTER(len=1), DIMENSION(3)  :: txts
101    CHARACTER(len=2), DIMENSION(9)  :: txtp
102    CHARACTER(len=23)               :: str1,str2
103 
104    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
105    INTEGER :: iq, new_iq, iiq, jq, ierr,itr
106    INTEGER :: ifils,ipere,generation ! CRisi
107    LOGICAL :: continu,nouveau_traceurdef
108    INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def
109    CHARACTER(len=30) :: tchaine   
110
111    character(len=*),parameter :: modname="infotrac_init"
112!-----------------------------------------------------------------------
113! Initialization :
114!
115    txts=(/'x','y','z'/)
116    txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/)
117
118    descrq(14)='VLH'
119    descrq(10)='VL1'
120    descrq(11)='VLP'
121    descrq(12)='FH1'
122    descrq(13)='FH2'
123    descrq(16)='PPM'
124    descrq(17)='PPS'
125    descrq(18)='PPP'
126    descrq(20)='SLP'
127    descrq(30)='PRA'
128   
129
130    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
131    IF (type_trac=='inca') THEN
132       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
133            type_trac,' config_inca=',config_inca
134       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
135          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
136          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
137       END IF
138#ifndef INCA
139       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
140       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
141#endif
142    ELSE IF (type_trac=='repr') THEN
143       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
144#ifndef REPROBUS
145       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
146       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
147#endif
148    ELSE IF (type_trac == 'lmdz') THEN
149       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
150    ELSE
151       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
152       CALL abort_gcm('infotrac_init','bad parameter',1)
153    END IF
154
155
156    ! Test if config_inca is other then none for run without INCA
157    IF (type_trac/='inca' .AND. config_inca/='none') THEN
158       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
159       config_inca='none'
160    END IF
161
162
163!-----------------------------------------------------------------------
164!
165! 1) Get the true number of tracers + water vapor/liquid
166!    Here true tracers (nqtrue) means declared tracers (only first order)
167!
168!-----------------------------------------------------------------------
169    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
170       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
171       IF(ierr.EQ.0) THEN
172          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
173          READ(90,*) nqtrue
174          write(lunout,*) 'nqtrue=',nqtrue
175       ELSE
176          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
177          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
178          if (planet_type=='earth') then
179            nqtrue=4 ! Default value for Earth
180          else
181            nqtrue=1 ! Default value for other planets
182          endif
183       END IF
184!jyg<
185!!       if ( planet_type=='earth') then
186!!         ! For Earth, water vapour & liquid tracers are not in the physics
187!!         nbtr=nqtrue-2
188!!       else
189!!         ! Other planets (for now); we have the same number of tracers
190!!         ! in the dynamics than in the physics
191!!         nbtr=nqtrue
192!!       endif
193!>jyg
194    ELSE ! type_trac=inca
195!jyg<
196       ! The traceur.def file is used to define the number "nqo" of water phases
197       ! present in the simulation. Default : nqo = 2.
198       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
199       IF(ierr.EQ.0) THEN
200          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
201          READ(90,*) nqo
202       ELSE
203          WRITE(lunout,*) trim(modname),': Using default value for nqo'
204          nqo=2
205       ENDIF
206       IF (nqo /= 2 .AND. nqo /= 3 ) THEN
207          WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowded. Only 2 or 3 water phases allowed'
208          CALL abort_gcm('infotrac_init','Bad number of water phases',1)
209       END IF
210! On déplace ce qui suit plus bas, une fois qu'on connait nbtr retranché des
211! isotopes
212!       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
213!#ifdef INCA
214!       CALL Init_chem_inca_trac(nbtr)
215!#endif       
216!       nqtrue=nbtr+nqo
217!
218!       ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
219
220    END IF   ! type_trac
221!>jyg
222
223    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
224       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
225       CALL abort_gcm('infotrac_init','Not enough tracers',1)
226    END IF
227   
228!jyg<
229! Transfert number of tracers to Reprobus
230!!    IF (type_trac == 'repr') THEN
231!!#ifdef REPROBUS
232!!       CALL Init_chem_rep_trac(nbtr)
233!!#endif
234!!    END IF
235!>jyg
236       
237!
238! Allocate variables depending on nqtrue
239!
240    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue),tnom_transp(nqtrue))
241
242!
243!jyg<
244!!    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
245!!    conv_flg(:) = 1 ! convection activated for all tracers
246!!    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
247!>jyg
248
249!-----------------------------------------------------------------------
250! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
251!
252!     iadv = 1    schema  transport type "humidite specifique LMD"
253!     iadv = 2    schema   amont
254!     iadv = 14   schema  Van-leer + humidite specifique
255!                            Modif F.Codron
256!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
257!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
258!     iadv = 12   schema  Frederic Hourdin I
259!     iadv = 13   schema  Frederic Hourdin II
260!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
261!     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
262!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
263!     iadv = 20   schema  Slopes
264!     iadv = 30   schema  Prather
265!
266!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
267!                                     iq = 2  pour l'eau liquide
268!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
269!
270!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
271!------------------------------------------------------------------------
272!
273!    Get choice of advection schema from file tracer.def or from INCA
274!---------------------------------------------------------------------
275    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
276       IF(ierr.EQ.0) THEN
277          ! Continue to read tracer.def
278          DO iq=1,nqtrue
279
280             write(*,*) 'infotrac 237: iq=',iq
281             ! CRisi: ajout du nom du fluide transporteur
282             ! mais rester retro compatible
283             READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
284             write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
285             write(lunout,*) 'tchaine=',trim(tchaine)
286             write(*,*) 'infotrac 238: IOstatus=',IOstatus
287             if (IOstatus.ne.0) then
288                CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
289             endif
290             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
291             ! espace ou pas au milieu de la chaine.
292             continu=.true.
293             nouveau_traceurdef=.false.
294             iiq=1
295             do while (continu)
296                if (tchaine(iiq:iiq).eq.' ') then
297                  nouveau_traceurdef=.true.
298                  continu=.false.
299                else if (iiq.lt.LEN_TRIM(tchaine)) then
300                  iiq=iiq+1
301                else
302                  continu=.false.
303                endif
304             enddo
305             write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
306             if (nouveau_traceurdef) then
307                write(lunout,*) 'C''est la nouvelle version de traceur.def'
308                tnom_0(iq)=tchaine(1:iiq-1)
309                tnom_transp(iq)=tchaine(iiq+1:LEN_TRIM(tchaine))
310             else
311                write(lunout,*) 'C''est l''ancienne version de traceur.def'
312                write(lunout,*) 'On suppose que les traceurs sont tous d''air'
313                tnom_0(iq)=tchaine
314                tnom_transp(iq) = 'air'
315             endif
316             write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
317             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
318
319          END DO !DO iq=1,nqtrue
320          CLOSE(90) 
321
322       ELSE ! Without tracer.def, set default values
323         if (planet_type=="earth") then
324          ! for Earth, default is to have 4 tracers
325          hadv(1) = 14
326          vadv(1) = 14
327          tnom_0(1) = 'H2Ov'
328          tnom_transp(1) = 'air'
329          hadv(2) = 10
330          vadv(2) = 10
331          tnom_0(2) = 'H2Ol'
332          tnom_transp(2) = 'air'
333          hadv(3) = 10
334          vadv(3) = 10
335          tnom_0(3) = 'RN'
336          tnom_transp(3) = 'air'
337          hadv(4) = 10
338          vadv(4) = 10
339          tnom_0(4) = 'PB'
340          tnom_transp(4) = 'air'
341         else ! default for other planets
342          hadv(1) = 10
343          vadv(1) = 10
344          tnom_0(1) = 'dummy'
345          tnom_transp(1) = 'dummy'
346         endif ! of if (planet_type=="earth")
347       END IF
348       
349       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
350       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
351       DO iq=1,nqtrue
352          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq),tnom_transp(iq)
353       END DO
354
355       if ( planet_type=='earth') then
356         !CR: nombre de traceurs de l eau
357         if (tnom_0(3) == 'H2Oi') then
358            nqo=3
359         else
360            nqo=2
361         endif
362         ! For Earth, water vapour & liquid tracers are not in the physics
363         nbtr=nqtrue-nqo
364       else
365         ! Other planets (for now); we have the same number of tracers
366         ! in the dynamics than in the physics
367         nbtr=nqtrue
368       endif
369
370    ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr')
371!jyg<
372!
373! On déplace ce qui suit plus bas une fois qu'on a retranché les isotopes de
374! nbtr
375!! Transfert number of tracers to Reprobus
376!    IF (type_trac == 'repr') THEN
377!#ifdef REPROBUS
378!       CALL Init_chem_rep_trac(nbtr)
379!#endif
380!    END IF
381!
382! Allocate variables depending on nbtr
383!
384!    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
385!    conv_flg(:) = 1 ! convection activated for all tracers
386!    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
387!
388!!    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
389!
390    IF (type_trac == 'inca') THEN   ! config_inca='aero' ou 'chem'
391!>jyg
392! le module de chimie fournit les noms des traceurs
393! et les schemas d'advection associes. excepte pour ceux lus
394! dans traceur.def
395       IF (ierr .eq. 0) then
396          DO iq=1,nqo
397
398             write(*,*) 'infotrac 237: iq=',iq
399             ! CRisi: ajout du nom du fluide transporteur
400             ! mais rester retro compatible
401             READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
402             write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
403             write(lunout,*) 'tchaine=',trim(tchaine)
404             write(*,*) 'infotrac 238: IOstatus=',IOstatus
405             if (IOstatus.ne.0) then
406                CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
407             endif
408             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
409             ! espace ou pas au milieu de la chaine.
410             continu=.true.
411             nouveau_traceurdef=.false.
412             iiq=1
413             do while (continu)
414                if (tchaine(iiq:iiq).eq.' ') then
415                  nouveau_traceurdef=.true.
416                  continu=.false.
417                else if (iiq.lt.LEN_TRIM(tchaine)) then
418                  iiq=iiq+1
419                else
420                  continu=.false.
421                endif
422             enddo
423             write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
424             if (nouveau_traceurdef) then
425                write(lunout,*) 'C''est la nouvelle version de traceur.def'
426                tnom_0(iq)=tchaine(1:iiq-1)
427                tnom_transp(iq)=tchaine(iiq+1:LEN_TRIM(tchaine))
428             else
429                write(lunout,*) 'C''est l''ancienne version de traceur.def'
430                write(lunout,*) 'On suppose que les traceurs sont tous d''air'
431                tnom_0(iq)=tchaine
432                tnom_transp(iq) = 'air'
433             endif
434             write(lunout,*) 'infotrac 426: tnom_0(iq)=<',trim(tnom_0(iq)),'>'
435             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
436
437          END DO !DO iq=1,nqtrue
438          CLOSE(90) 
439       ELSE  !! if traceur.def doesn't exist
440          tnom_0(1)='H2Ov'
441          tnom_transp(1) = 'air'
442          tnom_0(2)='H2Ol'
443          tnom_transp(2) = 'air'
444          hadv(1) = 10
445          hadv(2) = 10
446          vadv(1) = 10
447          vadv(2) = 10
448       ENDIF
449 
450#ifdef INCA
451       CALL init_transport( &
452            hadv_inca, &
453            vadv_inca, &
454            conv_flg, &
455            pbl_flg,  &
456            solsym)
457#endif
458
459
460!jyg<
461       DO iq = nqo+1, nqtrue
462          hadv(iq) = hadv_inca(iq-nqo)
463          vadv(iq) = vadv_inca(iq-nqo)
464          tnom_0(iq)=solsym(iq-nqo)
465          tnom_transp(iq) = 'air'
466       END DO
467
468    END IF ! (type_trac == 'inca')
469
470!-----------------------------------------------------------------------
471!
472! 3) Verify if advection schema 20 or 30 choosen
473!    Calculate total number of tracers needed: nqtot
474!    Allocate variables depending on total number of tracers
475!-----------------------------------------------------------------------
476    new_iq=0
477    DO iq=1,nqtrue
478       ! Add tracers for certain advection schema
479       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
480          new_iq=new_iq+1  ! no tracers added
481       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
482          new_iq=new_iq+4  ! 3 tracers added
483       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
484          new_iq=new_iq+10 ! 9 tracers added
485       ELSE
486          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
487          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
488       END IF
489    END DO
490   
491    IF (new_iq /= nqtrue) THEN
492       ! The choice of advection schema imposes more tracers
493       ! Assigne total number of tracers
494       nqtot = new_iq
495
496       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
497       WRITE(lunout,*) 'makes it necessary to add tracers'
498       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
499       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
500
501    ELSE
502       ! The true number of tracers is also the total number
503       nqtot = nqtrue
504    END IF
505
506!
507! Allocate variables with total number of tracers, nqtot
508!
509    ALLOCATE(tname(nqtot), ttext(nqtot))
510    ALLOCATE(iadv(nqtot), niadv(nqtot))
511
512!-----------------------------------------------------------------------
513!
514! 4) Determine iadv, long and short name
515!
516!-----------------------------------------------------------------------
517    new_iq=0
518    DO iq=1,nqtrue
519       new_iq=new_iq+1
520
521       ! Verify choice of advection schema
522       IF (hadv(iq)==vadv(iq)) THEN
523          iadv(new_iq)=hadv(iq)
524       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
525          iadv(new_iq)=11
526       ELSE
527          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
528
529          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
530       END IF
531     
532       str1=tnom_0(iq)
533       tname(new_iq)= tnom_0(iq)
534       IF (iadv(new_iq)==0) THEN
535          ttext(new_iq)=trim(str1)
536       ELSE
537          ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
538       END IF
539
540       ! schemas tenant compte des moments d'ordre superieur
541       str2=ttext(new_iq)
542       IF (iadv(new_iq)==20) THEN
543          DO jq=1,3
544             new_iq=new_iq+1
545             iadv(new_iq)=-20
546             ttext(new_iq)=trim(str2)//txts(jq)
547             tname(new_iq)=trim(str1)//txts(jq)
548          END DO
549       ELSE IF (iadv(new_iq)==30) THEN
550          DO jq=1,9
551             new_iq=new_iq+1
552             iadv(new_iq)=-30
553             ttext(new_iq)=trim(str2)//txtp(jq)
554             tname(new_iq)=trim(str1)//txtp(jq)
555          END DO
556       END IF
557    END DO
558
559!
560! Find vector keeping the correspodence between true and total tracers
561!
562    niadv(:)=0
563    iiq=0
564    DO iq=1,nqtot
565       IF(iadv(iq).GE.0) THEN
566          ! True tracer
567          iiq=iiq+1
568          niadv(iiq)=iq
569       ENDIF
570    END DO
571
572
573    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
574    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
575    DO iq=1,nqtot
576       WRITE(lunout,*) iadv(iq),niadv(iq),&
577       ' ',trim(tname(iq)),' ',trim(ttext(iq))
578    END DO
579
580!
581! Test for advection schema.
582! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
583!
584    DO iq=1,nqtot
585       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
586          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
587          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
588       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
589          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
590          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
591       END IF
592    END DO
593
594
595! CRisi: quels sont les traceurs fils et les traceurs pères.
596! initialiser tous les tableaux d'indices liés aux traceurs familiaux
597! + vérifier que tous les pères sont écrits en premières positions
598    ALLOCATE(nqfils(nqtot),nqdesc(nqtot))   
599    ALLOCATE(iqfils(nqtot,nqtot))   
600    ALLOCATE(iqpere(nqtot))
601    nqperes=0
602    nqfils(:)=0
603    nqdesc(:)=0
604    iqfils(:,:)=0
605    iqpere(:)=0
606    nqdesc_tot=0   
607    DO iq=1,nqtot
608      if (tnom_transp(iq) == 'air') then
609        ! ceci est un traceur père
610        WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un pere'
611        nqperes=nqperes+1
612        iqpere(iq)=0
613      else !if (tnom_transp(iq) == 'air') then
614        ! ceci est un fils. Qui est son père?
615        WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un fils'
616        continu=.true.
617        ipere=1
618        do while (continu)   
619          write(lunout,*) 'infotrac 610: ipere,tnom_0(ipere)=',ipere,tnom_0(ipere)
620          write(lunout,*) 'tnom_transp(iq)=',tnom_transp(iq)       
621          if (tnom_transp(iq) == tnom_0(ipere)) then
622            ! Son père est ipere
623            WRITE(lunout,*) 'Le traceur',iq,'appele ', &
624      &          trim(tnom_0(iq)),' est le fils de ',ipere,'appele ',trim(tnom_0(ipere))
625            if (iq.eq.ipere) then
626                CALL abort_gcm('infotrac_init','Un fils est son propre pere',1)
627            endif
628            nqfils(ipere)=nqfils(ipere)+1 
629            iqfils(nqfils(ipere),ipere)=iq
630            iqpere(iq)=ipere         
631            continu=.false.
632          else !if (tnom_transp(iq) == tnom_0(ipere)) then
633            ipere=ipere+1
634            if (ipere.gt.nqtot) then
635                WRITE(lunout,*) 'Le traceur',iq,'appele ', &
636      &          trim(tnom_0(iq)),', est orpelin.'
637                write(lunout,*) 'ipere,nqtot=',ipere,nqtot
638                CALL abort_gcm('infotrac_init','Un traceur est orphelin',1)
639            endif !if (ipere.gt.nqtot) then
640          endif !if (tnom_transp(iq) == tnom_0(ipere)) then
641        enddo !do while (continu)
642      endif !if (tnom_transp(iq) == 'air') then
643    enddo !DO iq=1,nqtot
644    WRITE(lunout,*) 'infotrac: nqperes=',nqperes   
645    WRITE(lunout,*) 'nqfils=',nqfils
646    WRITE(lunout,*) 'iqpere=',iqpere
647    WRITE(lunout,*) 'iqfils=',iqfils
648
649! Calculer le nombre de descendants à partir de iqfils et de nbfils
650    DO iq=1,nqtot   
651      generation=0
652      continu=.true.
653      ifils=iq
654      do while (continu)
655        ipere=iqpere(ifils)
656        if (ipere.gt.0) then
657         nqdesc(ipere)=nqdesc(ipere)+1   
658         nqdesc_tot=nqdesc_tot+1     
659         iqfils(nqdesc(ipere),ipere)=iq
660         ifils=ipere
661         generation=generation+1
662        else !if (ipere.gt.0) then
663         continu=.false.
664        endif !if (ipere.gt.0) then
665      enddo !do while (continu)   
666      WRITE(lunout,*) 'Le traceur ',iq,', appele ',trim(tnom_0(iq)),' est un traceur de generation: ',generation
667    enddo !DO iq=1,nqtot
668    WRITE(lunout,*) 'infotrac: nqdesc=',nqdesc
669    WRITE(lunout,*) 'iqfils=',iqfils
670    WRITE(lunout,*) 'nqdesc_tot=',nqdesc_tot
671
672! Interdire autres schémas que 10 pour les traceurs fils, et autres schémas
673! que 10 et 14 si des pères ont des fils
674    do iq=1,nqtot
675      if (iqpere(iq).gt.0) then
676        ! ce traceur a un père qui n'est pas l'air
677        ! Seul le schéma 10 est autorisé
678        if (iadv(iq)/=10) then
679           WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not implemented for sons'
680          CALL abort_gcm('infotrac_init','Sons should be advected by scheme 10',1)
681        endif
682        ! Le traceur père ne peut être advecté que par schéma 10 ou 14:
683        IF (iadv(iqpere(iq))/=10 .AND. iadv(iqpere(iq))/=14) THEN
684          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not implemented for fathers'
685          CALL abort_gcm('infotrac_init','Fathers should be advected by scheme 10 ou 14',1)
686        endif !IF (iadv(iqpere(iq))/=10 .AND. iadv(iqpere(iq))/=14) THEN
687     endif !if (iqpere(iq).gt.0) the
688    enddo !do iq=1,nqtot
689
690
691! detecter quels sont les traceurs isotopiques parmi des traceurs
692    call infotrac_isoinit(tnom_0,nqtrue)
693
694    if (ntraciso.gt.0) then
695! retrancher les traceurs isotopiques de la liste des traceurs qui passent dans
696! phytrac
697        nbtr=nbtr-nqo*ntraciso
698
699! faire un tableau d'indice des traceurs qui passeront dans phytrac
700        nqtottr=nqtot-nqo*(1+ntraciso)
701        write(*,*) 'infotrac 704: nqtottr,nqtot,nqo=',nqtottr,nqtot,nqo
702        ! Rq: nqtottr n'est pas forcément égal à nbtr dans le cas où new_iq /= nqtrue
703        ALLOCATE (itr_indice(nqtot)) 
704        itr_indice(:)=0 
705        itr=0
706        do iq=nqo+1, nqtot
707          if (iso_num(iq).eq.0) then
708            itr=itr+1
709            write(*,*) 'itr=',itr
710            itr_indice(itr)=iq
711          endif !if (iso_num(iq).eq.0) then
712        enddo
713        if (itr.ne.nqtottr) then
714            CALL abort_gcm('infotrac_init','pb dans le calcul de nqtottr',1)
715        endif
716    endif !if (ntraciso.gt.0) then
717
718! on déplace les initialisations de REPROBUS ou INCA ici, avec la nouvelle
719! valeur de nbtr
720
721     if (type_trac == 'inca') then
722       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
723#ifdef INCA
724       CALL Init_chem_inca_trac(nbtr)
725#endif       
726       nqtrue=nbtr+nqo
727
728       ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
729    endif
730
731! Transfert number of tracers to Reprobus
732    IF (type_trac == 'repr') THEN
733#ifdef REPROBUS
734       CALL Init_chem_rep_trac(nbtr)
735#endif
736    END IF
737!
738! Allocate variables depending on nbtr
739!
740    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
741    conv_flg(:) = 1 ! convection activated for all tracers
742    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
743
744       
745!-----------------------------------------------------------------------
746! Finalize :
747!
748    DEALLOCATE(tnom_0, hadv, vadv,tnom_transp)
749
750
751  END SUBROUTINE infotrac_init
752
753  SUBROUTINE infotrac_isoinit(tnom_0,nqtrue)
754
755#ifdef CPP_IOIPSL
756  use IOIPSL
757#else
758  ! if not using IOIPSL, we still need to use (a local version of) getin
759  use ioipsl_getincom
760#endif
761  implicit none
762 
763    ! inputs
764    INTEGER nqtrue
765    CHARACTER(len=15) tnom_0(nqtrue)
766   
767    ! locals   
768    CHARACTER(len=3), DIMENSION(niso_possibles) :: tnom_iso
769    INTEGER, ALLOCATABLE,DIMENSION(:,:) :: nb_iso,nb_traciso
770    INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind
771    INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone
772    CHARACTER(len=19) :: tnom_trac
773    INCLUDE "iniprint.h"
774
775    tnom_iso=(/'eau','HDO','O18','O17','HTO'/)
776
777    ALLOCATE(nb_iso(niso_possibles,nqo))
778    ALLOCATE(nb_isoind(nqo))
779    ALLOCATE(nb_traciso(niso_possibles,nqo))
780    ALLOCATE(iso_num(nqtot))
781    ALLOCATE(iso_indnum(nqtot))
782    ALLOCATE(zone_num(nqtot))
783    ALLOCATE(phase_num(nqtot))
784     
785    iso_num(:)=0
786    iso_indnum(:)=0
787    zone_num(:)=0
788    phase_num(:)=0
789    indnum_fn_num(:)=0
790    use_iso(:)=.false. 
791    nb_iso(:,:)=0 
792    nb_isoind(:)=0     
793    nb_traciso(:,:)=0
794    niso=0
795    ntraceurs_zone=0 
796    ntraceurs_zone_prec=0
797    ntraciso=0
798
799    do iq=nqo+1,nqtot
800       write(lunout,*) 'infotrac 569: iq,tnom_0(iq)=',iq,tnom_0(iq)
801       do phase=1,nqo   
802        do ixt= 1,niso_possibles   
803         tnom_trac=trim(tnom_0(phase))//'_'
804         tnom_trac=trim(tnom_trac)//trim(tnom_iso(ixt))
805         write(*,*) 'phase,ixt,tnom_trac=',phase,ixt,tnom_trac     
806         IF (tnom_0(iq) == tnom_trac) then
807          write(lunout,*) 'Ce traceur est un isotope'
808          nb_iso(ixt,phase)=nb_iso(ixt,phase)+1   
809          nb_isoind(phase)=nb_isoind(phase)+1   
810          iso_num(iq)=ixt
811          iso_indnum(iq)=nb_isoind(phase)
812          indnum_fn_num(ixt)=iso_indnum(iq)
813          phase_num(iq)=phase
814          write(lunout,*) 'iso_num(iq)=',iso_num(iq)
815          write(lunout,*) 'iso_indnum(iq)=',iso_indnum(iq)
816          write(lunout,*) 'indnum_fn_num(ixt)=',indnum_fn_num(ixt)
817          write(lunout,*) 'phase_num(iq)=',phase_num(iq)
818          goto 20
819         else if (iqpere(iq).gt.0) then         
820          if (tnom_0(iqpere(iq)) == tnom_trac) then
821           write(lunout,*) 'Ce traceur est le fils d''un isotope'
822           ! c'est un traceur d'isotope
823           nb_traciso(ixt,phase)=nb_traciso(ixt,phase)+1
824           iso_num(iq)=ixt
825           iso_indnum(iq)=indnum_fn_num(ixt)
826           zone_num(iq)=nb_traciso(ixt,phase)
827           phase_num(iq)=phase
828           write(lunout,*) 'iso_num(iq)=',iso_num(iq)
829           write(lunout,*) 'phase_num(iq)=',phase_num(iq)
830           write(lunout,*) 'zone_num(iq)=',zone_num(iq)
831           goto 20
832          endif !if (tnom_0(iqpere(iq)) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
833         endif !IF (tnom_0(iq) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
834        enddo !do ixt= niso_possibles
835       enddo !do phase=1,nqo
836  20   continue
837      enddo !do iq=1,nqtot
838
839      write(lunout,*) 'iso_num=',iso_num
840      write(lunout,*) 'iso_indnum=',iso_indnum
841      write(lunout,*) 'zone_num=',zone_num 
842      write(lunout,*) 'phase_num=',phase_num
843      write(lunout,*) 'indnum_fn_num=',indnum_fn_num
844      write(lunout,*) 'nb_iso=',nb_iso
845
846      do ixt= 1,niso_possibles 
847
848        if (nb_iso(ixt,1).eq.1) then
849          ! on vérifie que toutes les phases ont le même nombre de
850          ! traceurs
851          do phase=2,nqo
852            if (nb_iso(ixt,phase).ne.nb_iso(ixt,1)) then
853!              write(lunout,*) 'ixt,phase,nb_iso=',ixt,phase,nb_iso(ixt,phase)
854              CALL abort_gcm('infotrac_init','Phases must have same number of isotopes',1)
855            endif
856          enddo !do phase=2,nqo
857
858          niso=niso+1
859          use_iso(ixt)=.true.
860          ntraceurs_zone=nb_traciso(ixt,1)
861
862          ! on vérifie que toutes les phases ont le même nombre de
863          ! traceurs
864          do phase=2,nqo
865            if (nb_traciso(ixt,phase).ne.ntraceurs_zone) then
866              write(lunout,*) 'ixt,phase,nb_traciso=',ixt,phase,nb_traciso(ixt,phase)
867              write(lunout,*) 'ntraceurs_zone=',ntraceurs_zone
868              CALL abort_gcm('infotrac_init','Phases must have same number of tracers',1)
869            endif 
870          enddo  !do phase=2,nqo
871          ! on vérifie que tous les isotopes ont le même nombre de
872          ! traceurs
873          if (ntraceurs_zone_prec.gt.0) then               
874            if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
875              ntraceurs_zone_prec=ntraceurs_zone
876            else !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
877              write(*,*) 'ntraceurs_zone_prec,ntraceurs_zone=',ntraceurs_zone_prec,ntraceurs_zone   
878              CALL abort_gcm('infotrac_init', &
879               &'Isotope tracers are not well defined in traceur.def',1)           
880            endif !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
881           endif !if (ntraceurs_zone_prec.gt.0) then
882
883        else if (nb_iso(ixt,1).ne.0) then
884           WRITE(lunout,*) 'nqo,ixt=',nqo,ixt
885           WRITE(lunout,*) 'nb_iso(ixt,1)=',nb_iso(ixt,1)   
886           CALL abort_gcm('infotrac_init','Isotopes are not well defined in traceur.def',1)     
887        endif   !if (nb_iso(ixt,1).eq.1) then       
888    enddo ! do ixt= niso_possibles
889
890    ! dimensions isotopique:
891    ntraciso=niso*(ntraceurs_zone+1)
892    WRITE(lunout,*) 'niso=',niso
893    WRITE(lunout,*) 'ntraceurs_zone,ntraciso=',ntraceurs_zone,ntraciso 
894    WRITE(lunout,*) 'use_iso=',use_iso 
895 
896    ! flags isotopiques:
897    if (niso.gt.0) then
898        ok_isotopes=.true.
899    else
900        ok_isotopes=.false.
901    endif
902    WRITE(lunout,*) 'infotrac 837: ok_isotopes=',ok_isotopes
903 
904    if (ok_isotopes) then
905        ok_iso_verif=.false.
906        call getin('ok_iso_verif',ok_iso_verif)
907        ok_init_iso=.false.
908        call getin('ok_init_iso',ok_init_iso)
909        tnat=(/1.0,155.76e-6,2005.2e-6,0.004/100.,0.0/)
910        alpha_ideal=(/1.0,1.01,1.006,1.003,1.0/)
911    endif !if (ok_isotopes) then 
912!    WRITE(lunout,*) 'ok_iso_verif=',ok_iso_verif
913!    WRITE(lunout,*) 'ok_init_iso=',ok_init_iso
914
915    if (ntraceurs_zone.gt.0) then
916        ok_isotrac=.true.
917    else
918        ok_isotrac=.false.
919    endif   
920!    WRITE(lunout,*) 'ok_isotrac=',ok_isotrac
921
922    ! remplissage du tableau iqiso(ntraciso,phase)
923    ALLOCATE(iqiso(ntraciso,nqo))   
924    iqiso(:,:)=0     
925    do iq=1,nqtot
926        if (iso_num(iq).gt.0) then
927          ixt=iso_indnum(iq)+zone_num(iq)*niso
928          iqiso(ixt,phase_num(iq))=iq
929        endif
930    enddo
931!    WRITE(lunout,*) 'iqiso=',iqiso
932
933    ! replissage du tableau index_trac(ntraceurs_zone,niso)
934    ALLOCATE(index_trac(ntraceurs_zone,niso)) 
935    if (ok_isotrac) then
936        do iiso=1,niso
937          do izone=1,ntraceurs_zone
938             index_trac(izone,iiso)=iiso+izone*niso
939          enddo
940        enddo
941    else !if (ok_isotrac) then     
942        index_trac(:,:)=0.0
943    endif !if (ok_isotrac) then
944!    write(lunout,*) 'index_trac=',index_trac   
945
946! Finalize :
947    DEALLOCATE(nb_iso)
948
949  END SUBROUTINE infotrac_isoinit
950
951END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.