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

Last change on this file since 1446 was 1446, checked in by Ehouarn Millour, 14 years ago

Implemented modifications to enable running with only one tracer for planet types different from "earth". Rem: If flag 'planet_type' is set to "earth" (default behaviour) then there must be at least 2 tracers for the dynamics to function properly.

These updates do not induce any changes in model outputs with respect to previous revisions.

EM

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