source: LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/infotrac.F90 @ 1443

Last change on this file since 1443 was 1443, checked in by jghattas, 14 years ago

Small bug.

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