source: LMDZ5/trunk/libf/dyn3d_common/infotrac.F90 @ 2264

Last change on this file since 2264 was 2262, checked in by jyg, 9 years ago

Correction of a bug concerning the number 'nqo' of
water phases transported by the dynamic : the
default value (= 2, corresponding to vapour and
liquid phases) was still explicitely present in
various places.

Modified files:

infotrac.F90,
physiq.F90

  • 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: 15.7 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! Name variables
15  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
16  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
17
18! iadv  : index of trasport schema for each tracer
19  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
20
21! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
22!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
23  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
24
25! conv_flg(it)=0 : convection desactivated for tracer number it
26  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
27! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
28  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
29
30  CHARACTER(len=4),SAVE :: type_trac
31  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
32 
33CONTAINS
34
35  SUBROUTINE infotrac_init
36    USE control_mod
37#ifdef REPROBUS
38    USE CHEM_REP, ONLY : Init_chem_rep_trac
39#endif
40    IMPLICIT NONE
41!=======================================================================
42!
43!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
44!   -------
45!   Modif special traceur F.Forget 05/94
46!   Modif M-A Filiberti 02/02 lecture de traceur.def
47!
48!   Objet:
49!   ------
50!   GCM LMD nouvelle grille
51!
52!=======================================================================
53!   ... modification de l'integration de q ( 26/04/94 ) ....
54!-----------------------------------------------------------------------
55! Declarations
56
57    INCLUDE "dimensions.h"
58    INCLUDE "iniprint.h"
59
60! Local variables
61    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
62    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
63
64    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
65    CHARACTER(len=3), DIMENSION(30) :: descrq
66    CHARACTER(len=1), DIMENSION(3)  :: txts
67    CHARACTER(len=2), DIMENSION(9)  :: txtp
68    CHARACTER(len=23)               :: str1,str2
69 
70    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
71    INTEGER :: iq, new_iq, iiq, jq, ierr
72
73    character(len=*),parameter :: modname="infotrac_init"
74!-----------------------------------------------------------------------
75! Initialization :
76!
77    txts=(/'x','y','z'/)
78    txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/)
79
80    descrq(14)='VLH'
81    descrq(10)='VL1'
82    descrq(11)='VLP'
83    descrq(12)='FH1'
84    descrq(13)='FH2'
85    descrq(16)='PPM'
86    descrq(17)='PPS'
87    descrq(18)='PPP'
88    descrq(20)='SLP'
89    descrq(30)='PRA'
90   
91
92    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
93    IF (type_trac=='inca') THEN
94       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
95            type_trac,' config_inca=',config_inca
96       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
97          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
98          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
99       END IF
100#ifndef INCA
101       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
102       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
103#endif
104    ELSE IF (type_trac=='repr') THEN
105       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
106#ifndef REPROBUS
107       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
108       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
109#endif
110    ELSE IF (type_trac == 'lmdz') THEN
111       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
112    ELSE
113       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
114       CALL abort_gcm('infotrac_init','bad parameter',1)
115    END IF
116
117
118    ! Test if config_inca is other then none for run without INCA
119    IF (type_trac/='inca' .AND. config_inca/='none') THEN
120       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
121       config_inca='none'
122    END IF
123
124
125!-----------------------------------------------------------------------
126!
127! 1) Get the true number of tracers + water vapor/liquid
128!    Here true tracers (nqtrue) means declared tracers (only first order)
129!
130!-----------------------------------------------------------------------
131    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
132       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
133       IF(ierr.EQ.0) THEN
134          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
135          READ(90,*) nqtrue
136       ELSE
137          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
138          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
139          if (planet_type=='earth') then
140            nqtrue=4 ! Default value for Earth
141          else
142            nqtrue=1 ! Default value for other planets
143          endif
144       END IF
145!jyg<
146!!       if ( planet_type=='earth') then
147!!         ! For Earth, water vapour & liquid tracers are not in the physics
148!!         nbtr=nqtrue-2
149!!       else
150!!         ! Other planets (for now); we have the same number of tracers
151!!         ! in the dynamics than in the physics
152!!         nbtr=nqtrue
153!!       endif
154!>jyg
155    ELSE ! type_trac=inca
156!jyg<
157       ! The traceur.def file is used to define the number "nqo" of water phases
158       ! present in the simulation. Default : nqo = 2.
159       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
160       IF(ierr.EQ.0) THEN
161          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
162          READ(90,*) nqo
163       ELSE
164          WRITE(lunout,*) trim(modname),': Using default value for nqo'
165          nqo=2
166       ENDIF
167       IF (nqo /= 2 .OR. nqo /= 3 ) THEN
168          WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowded. Only 2 or 3 water phases allowed'
169          CALL abort_gcm('infotrac_init','Bad number of water phases',1)
170       END IF
171       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
172       nqtrue=nbtr+nqo
173!!       nqtrue=nbtr+2
174    END IF   ! type_trac
175!>jyg
176
177    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
178       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
179       CALL abort_gcm('infotrac_init','Not enough tracers',1)
180    END IF
181   
182!jyg<
183! Transfert number of tracers to Reprobus
184!!    IF (type_trac == 'repr') THEN
185!!#ifdef REPROBUS
186!!       CALL Init_chem_rep_trac(nbtr)
187!!#endif
188!!    END IF
189!>jyg
190       
191!
192! Allocate variables depending on nqtrue
193!
194    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
195!
196!jyg<
197!!    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
198!!    conv_flg(:) = 1 ! convection activated for all tracers
199!!    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
200!>jyg
201
202!-----------------------------------------------------------------------
203! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
204!
205!     iadv = 1    schema  transport type "humidite specifique LMD"
206!     iadv = 2    schema   amont
207!     iadv = 14   schema  Van-leer + humidite specifique
208!                            Modif F.Codron
209!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
210!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
211!     iadv = 12   schema  Frederic Hourdin I
212!     iadv = 13   schema  Frederic Hourdin II
213!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
214!     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
215!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
216!     iadv = 20   schema  Slopes
217!     iadv = 30   schema  Prather
218!
219!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
220!                                     iq = 2  pour l'eau liquide
221!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
222!
223!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
224!------------------------------------------------------------------------
225!
226!    Get choice of advection schema from file tracer.def or from INCA
227!---------------------------------------------------------------------
228    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
229       IF(ierr.EQ.0) THEN
230          ! Continue to read tracer.def
231          DO iq=1,nqtrue
232             READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
233          END DO
234          CLOSE(90) 
235       ELSE ! Without tracer.def, set default values
236         if (planet_type=="earth") then
237          ! for Earth, default is to have 4 tracers
238          hadv(1) = 14
239          vadv(1) = 14
240          tnom_0(1) = 'H2Ov'
241          hadv(2) = 10
242          vadv(2) = 10
243          tnom_0(2) = 'H2Ol'
244          hadv(3) = 10
245          vadv(3) = 10
246          tnom_0(3) = 'RN'
247          hadv(4) = 10
248          vadv(4) = 10
249          tnom_0(4) = 'PB'
250         else ! default for other planets
251          hadv(1) = 10
252          vadv(1) = 10
253          tnom_0(1) = 'dummy'
254         endif ! of if (planet_type=="earth")
255       END IF
256       
257       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
258       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
259       DO iq=1,nqtrue
260          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
261       END DO
262
263       if ( planet_type=='earth') then
264         !CR: nombre de traceurs de l eau
265         if (tnom_0(3) == 'H2Oi') then
266            nqo=3
267         else
268            nqo=2
269         endif
270         ! For Earth, water vapour & liquid tracers are not in the physics
271         nbtr=nqtrue-nqo
272       else
273         ! Other planets (for now); we have the same number of tracers
274         ! in the dynamics than in the physics
275         nbtr=nqtrue
276       endif
277
278    ENDIF  ! (type_trac == 'lmdz' .OR. type_trac == 'repr')
279!jyg<
280!
281! Transfert number of tracers to Reprobus
282    IF (type_trac == 'repr') THEN
283#ifdef REPROBUS
284       CALL Init_chem_rep_trac(nbtr)
285#endif
286    END IF
287!
288! Allocate variables depending on nbtr
289!
290    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
291    conv_flg(:) = 1 ! convection activated for all tracers
292    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
293!
294!!    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
295!
296    IF (type_trac == 'inca') THEN   ! config_inca='aero' ou 'chem'
297!>jyg
298! le module de chimie fournit les noms des traceurs
299! et les schemas d'advection associes.
300     
301#ifdef INCA
302       CALL init_transport( &
303            hadv, &
304            vadv, &
305            conv_flg, &
306            pbl_flg,  &
307            solsym)
308#endif
309       tnom_0(1)='H2Ov'
310       tnom_0(2)='H2Ol'
311       IF (nqo == 3) tnom_0(3)='H2Oi'     !! jyg
312
313!jyg<
314       DO iq = nqo+1, nqtrue
315          tnom_0(iq)=solsym(iq-nqo)
316       END DO
317!!       DO iq =3,nqtrue
318!!          tnom_0(iq)=solsym(iq-2)
319!!       END DO
320!!       nqo = 2
321!>jyg
322
323    END IF ! (type_trac == 'inca')
324
325!-----------------------------------------------------------------------
326!
327! 3) Verify if advection schema 20 or 30 choosen
328!    Calculate total number of tracers needed: nqtot
329!    Allocate variables depending on total number of tracers
330!-----------------------------------------------------------------------
331    new_iq=0
332    DO iq=1,nqtrue
333       ! Add tracers for certain advection schema
334       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
335          new_iq=new_iq+1  ! no tracers added
336       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
337          new_iq=new_iq+4  ! 3 tracers added
338       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
339          new_iq=new_iq+10 ! 9 tracers added
340       ELSE
341          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
342          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
343       END IF
344    END DO
345   
346    IF (new_iq /= nqtrue) THEN
347       ! The choice of advection schema imposes more tracers
348       ! Assigne total number of tracers
349       nqtot = new_iq
350
351       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
352       WRITE(lunout,*) 'makes it necessary to add tracers'
353       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
354       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
355
356    ELSE
357       ! The true number of tracers is also the total number
358       nqtot = nqtrue
359    END IF
360
361!
362! Allocate variables with total number of tracers, nqtot
363!
364    ALLOCATE(tname(nqtot), ttext(nqtot))
365    ALLOCATE(iadv(nqtot), niadv(nqtot))
366
367!-----------------------------------------------------------------------
368!
369! 4) Determine iadv, long and short name
370!
371!-----------------------------------------------------------------------
372    new_iq=0
373    DO iq=1,nqtrue
374       new_iq=new_iq+1
375
376       ! Verify choice of advection schema
377       IF (hadv(iq)==vadv(iq)) THEN
378          iadv(new_iq)=hadv(iq)
379       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
380          iadv(new_iq)=11
381       ELSE
382          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
383
384          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
385       END IF
386     
387       str1=tnom_0(iq)
388       tname(new_iq)= tnom_0(iq)
389       IF (iadv(new_iq)==0) THEN
390          ttext(new_iq)=trim(str1)
391       ELSE
392          ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
393       END IF
394
395       ! schemas tenant compte des moments d'ordre superieur
396       str2=ttext(new_iq)
397       IF (iadv(new_iq)==20) THEN
398          DO jq=1,3
399             new_iq=new_iq+1
400             iadv(new_iq)=-20
401             ttext(new_iq)=trim(str2)//txts(jq)
402             tname(new_iq)=trim(str1)//txts(jq)
403          END DO
404       ELSE IF (iadv(new_iq)==30) THEN
405          DO jq=1,9
406             new_iq=new_iq+1
407             iadv(new_iq)=-30
408             ttext(new_iq)=trim(str2)//txtp(jq)
409             tname(new_iq)=trim(str1)//txtp(jq)
410          END DO
411       END IF
412    END DO
413
414!
415! Find vector keeping the correspodence between true and total tracers
416!
417    niadv(:)=0
418    iiq=0
419    DO iq=1,nqtot
420       IF(iadv(iq).GE.0) THEN
421          ! True tracer
422          iiq=iiq+1
423          niadv(iiq)=iq
424       ENDIF
425    END DO
426
427
428    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
429    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
430    DO iq=1,nqtot
431       WRITE(lunout,*) iadv(iq),niadv(iq),&
432       ' ',trim(tname(iq)),' ',trim(ttext(iq))
433    END DO
434
435!
436! Test for advection schema.
437! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
438!
439    DO iq=1,nqtot
440       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
441          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
442          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
443       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
444          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
445          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
446       END IF
447    END DO
448
449!-----------------------------------------------------------------------
450! Finalize :
451!
452    DEALLOCATE(tnom_0, hadv, vadv)
453
454
455  END SUBROUTINE infotrac_init
456
457END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.