source: trunk/LMDZ.COMMON/libf/dyn3d_common/infotrac.F90 @ 1508

Last change on this file since 1508 was 1508, checked in by emillour, 9 years ago

Common dynamics:
Updates in the dynamics (seq and ) to keep up with updates
in LMDZ5 (up to LMDZ5 trunk, rev 2325):
IMPORTANT: Modifications for isotopes are only done in dyn3d, not in dyn3dpar

as in LMDZ5 these modifications were done in dyn3dmem.
Related LMDZ5 revisions are r2270 and r2281

  • in dynlonlat_phylonlat:
  • add module "grid_atob_m.F90" (a regridding utility so far only used by phylmd/ce0l.F90, used to be dyn3d_common/grid_atob.F)
  • in misc:
  • follow up updates on wxios.F (add missing_val module variable)
  • in dyn3d_common:
  • pression.F => pression.F90
  • misc_mod.F90: moved from misc to dyn3d_common
  • added new iso_verif_dyn.F
  • covcont.F => covcont.F90
  • infotrac.F90 : add handling of isotopes (reading of corresponding traceur.def for planets not implemented)
  • dynetat0.F => dynetat0.F90 with some code factorization
  • dynredem.F => dynredem.F90 with some code factorization
  • added dynredem_mod.F90: routines used by dynredem
  • iniacademic.F90 : added isotopes-related initialization for Earth case
  • in dyn3d:
  • added check_isotopes.F
  • modified (isotopes) advtrac.F90, caladvtrac.F
  • guide_mod.F90: ported updates
  • leapfrog.F : (isotopes) updates (NB: call integrd with nqtot tracers)
  • qminimium.F : adaptations for isotopes (copied over, except that #include comvert.h is not needed).
  • vlsplt.F: adaptations for isotopes (copied over, except than #include logic.h, comvert.h not needed, and replace "include comconst.h" with use comconst_mod, ONLY: pi)
  • vlspltqs.F : same as vlsplt.F, but also keeping added modification for CP(T)
  • in dyn3dpar:
  • leapfrog_p.F: remove unecessary #ifdef CPP_EARTH cpp flag. and call integrd_p with nqtot tracers (only important for Earth)
  • dynredem_p.F => dynredem_p.F90 and some code factorization
  • and no isotopes-relates changes in dyn3dpar (since these changes have been made in LMDZ5 dyn3dmem).

EM

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