source: LMDZ5/trunk/libf/dyn3dpar/infotrac.F90 @ 1563

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