source: LMDZ5/branches/LMDZ6_rc0/libf/dyn3d_common/infotrac.F90 @ 5421

Last change on this file since 5421 was 2575, checked in by acozic, 10 years ago

for the VLR configuration add some modification from the trunk to fit with INCA version use

  • 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: 13.9 KB
RevLine 
[1279]1! $Id$
2!
[1114]3MODULE infotrac
4
5! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
6  INTEGER, SAVE :: nqtot
[2160]7!CR: on ajoute le nombre de traceurs de l eau
8  INTEGER, SAVE :: nqo
[1114]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
[1279]25! conv_flg(it)=0 : convection desactivated for tracer number it
[1114]26  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
[1279]27! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
[1114]28  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
29
[1279]30  CHARACTER(len=4),SAVE :: type_trac
[2381]31  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
[1279]32 
[1114]33CONTAINS
34
35  SUBROUTINE infotrac_init
[1403]36    USE control_mod
[1565]37#ifdef REPROBUS
38    USE CHEM_REP, ONLY : Init_chem_rep_trac
39#endif
[1114]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
[1279]64    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
[1114]65    CHARACTER(len=3), DIMENSION(30) :: descrq
66    CHARACTER(len=1), DIMENSION(3)  :: txts
67    CHARACTER(len=2), DIMENSION(9)  :: txtp
[1454]68    CHARACTER(len=23)               :: str1,str2
[1114]69 
70    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
71    INTEGER :: iq, new_iq, iiq, jq, ierr
[1454]72
73    character(len=*),parameter :: modname="infotrac_init"
[1114]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'
[1279]90   
[1114]91
[1569]92    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
[1563]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
[2381]96       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
[1563]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
[1569]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
[1565]104    ELSE IF (type_trac=='repr') THEN
105       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
[1569]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
[1563]110    ELSE IF (type_trac == 'lmdz') THEN
111       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
[1279]112    ELSE
[1563]113       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
114       CALL abort_gcm('infotrac_init','bad parameter',1)
[1279]115    END IF
116
[1563]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
[1114]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!-----------------------------------------------------------------------
[1565]131    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
[1114]132       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
133       IF(ierr.EQ.0) THEN
[1454]134          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
[1114]135          READ(90,*) nqtrue
136       ELSE
[1454]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
[1114]144       END IF
[1454]145       if ( planet_type=='earth') then
146         ! For Earth, water vapour & liquid tracers are not in the physics
147         nbtr=nqtrue-2
148       else
149         ! Other planets (for now); we have the same number of tracers
150         ! in the dynamics than in the physics
151         nbtr=nqtrue
152       endif
[1563]153    ELSE ! type_trac=inca
[2575]154#ifdef INCA
155       CALL Init_chem_inca_trac(nbtr)
156#endif       
[1114]157       nqtrue=nbtr+2
158    END IF
159
[1454]160    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
161       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
[1114]162       CALL abort_gcm('infotrac_init','Not enough tracers',1)
163    END IF
[1563]164   
[1565]165! Transfert number of tracers to Reprobus
166    IF (type_trac == 'repr') THEN
167#ifdef REPROBUS
168       CALL Init_chem_rep_trac(nbtr)
169#endif
170    END IF
[1563]171       
[1114]172!
[1279]173! Allocate variables depending on nqtrue and nbtr
[1114]174!
175    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
[2381]176    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
[1279]177    conv_flg(:) = 1 ! convection activated for all tracers
178    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
[1114]179
180!-----------------------------------------------------------------------
181! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
182!
183!     iadv = 1    schema  transport type "humidite specifique LMD"
184!     iadv = 2    schema   amont
185!     iadv = 14   schema  Van-leer + humidite specifique
186!                            Modif F.Codron
187!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
188!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
189!     iadv = 12   schema  Frederic Hourdin I
190!     iadv = 13   schema  Frederic Hourdin II
191!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
192!     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
193!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
194!     iadv = 20   schema  Slopes
195!     iadv = 30   schema  Prather
196!
197!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
198!                                     iq = 2  pour l'eau liquide
199!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
200!
201!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
202!------------------------------------------------------------------------
203!
204!    Get choice of advection schema from file tracer.def or from INCA
205!---------------------------------------------------------------------
[1565]206    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
[1114]207       IF(ierr.EQ.0) THEN
208          ! Continue to read tracer.def
209          DO iq=1,nqtrue
[1454]210             READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
[1114]211          END DO
212          CLOSE(90) 
[1454]213       ELSE ! Without tracer.def, set default values
214         if (planet_type=="earth") then
215          ! for Earth, default is to have 4 tracers
[1114]216          hadv(1) = 14
217          vadv(1) = 14
218          tnom_0(1) = 'H2Ov'
219          hadv(2) = 10
220          vadv(2) = 10
221          tnom_0(2) = 'H2Ol'
222          hadv(3) = 10
223          vadv(3) = 10
224          tnom_0(3) = 'RN'
225          hadv(4) = 10
226          vadv(4) = 10
227          tnom_0(4) = 'PB'
[1454]228         else ! default for other planets
229          hadv(1) = 10
230          vadv(1) = 10
231          tnom_0(1) = 'dummy'
232         endif ! of if (planet_type=="earth")
[1114]233       END IF
[2160]234
235!CR: nombre de traceurs de l eau
236       if (tnom_0(3) == 'H2Oi') then
237          nqo=3
238       else
239          nqo=2
240       endif
[1114]241       
[1454]242       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
243       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
[1114]244       DO iq=1,nqtrue
245          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
246       END DO
247
[1279]248    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
[1114]249! le module de chimie fournit les noms des traceurs
250! et les schemas d'advection associes.
251     
252#ifdef INCA
253       CALL init_transport( &
254            hadv, &
255            vadv, &
256            conv_flg, &
257            pbl_flg,  &
[2381]258            solsym)
[1114]259#endif
260       tnom_0(1)='H2Ov'
261       tnom_0(2)='H2Ol'
262
263       DO iq =3,nqtrue
[2381]264          tnom_0(iq)=solsym(iq-2)
[1114]265       END DO
[2160]266       nqo = 2
[1114]267
[1279]268    END IF ! type_trac
[1114]269
270!-----------------------------------------------------------------------
271!
272! 3) Verify if advection schema 20 or 30 choosen
273!    Calculate total number of tracers needed: nqtot
274!    Allocate variables depending on total number of tracers
275!-----------------------------------------------------------------------
276    new_iq=0
277    DO iq=1,nqtrue
278       ! Add tracers for certain advection schema
279       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
280          new_iq=new_iq+1  ! no tracers added
281       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
282          new_iq=new_iq+4  ! 3 tracers added
283       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
284          new_iq=new_iq+10 ! 9 tracers added
285       ELSE
[1454]286          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
[1114]287          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
288       END IF
289    END DO
290   
291    IF (new_iq /= nqtrue) THEN
292       ! The choice of advection schema imposes more tracers
293       ! Assigne total number of tracers
294       nqtot = new_iq
295
[1454]296       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
[1114]297       WRITE(lunout,*) 'makes it necessary to add tracers'
[1454]298       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
299       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
[1114]300
301    ELSE
302       ! The true number of tracers is also the total number
303       nqtot = nqtrue
304    END IF
305
306!
307! Allocate variables with total number of tracers, nqtot
308!
309    ALLOCATE(tname(nqtot), ttext(nqtot))
310    ALLOCATE(iadv(nqtot), niadv(nqtot))
311
312!-----------------------------------------------------------------------
313!
314! 4) Determine iadv, long and short name
315!
316!-----------------------------------------------------------------------
317    new_iq=0
318    DO iq=1,nqtrue
319       new_iq=new_iq+1
320
321       ! Verify choice of advection schema
322       IF (hadv(iq)==vadv(iq)) THEN
323          iadv(new_iq)=hadv(iq)
324       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
325          iadv(new_iq)=11
326       ELSE
[1454]327          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
328
[1114]329          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
330       END IF
331     
332       str1=tnom_0(iq)
333       tname(new_iq)= tnom_0(iq)
334       IF (iadv(new_iq)==0) THEN
[1454]335          ttext(new_iq)=trim(str1)
[1114]336       ELSE
[1454]337          ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
[1114]338       END IF
339
340       ! schemas tenant compte des moments d'ordre superieur
341       str2=ttext(new_iq)
342       IF (iadv(new_iq)==20) THEN
343          DO jq=1,3
344             new_iq=new_iq+1
345             iadv(new_iq)=-20
[1454]346             ttext(new_iq)=trim(str2)//txts(jq)
347             tname(new_iq)=trim(str1)//txts(jq)
[1114]348          END DO
349       ELSE IF (iadv(new_iq)==30) THEN
350          DO jq=1,9
351             new_iq=new_iq+1
352             iadv(new_iq)=-30
[1454]353             ttext(new_iq)=trim(str2)//txtp(jq)
354             tname(new_iq)=trim(str1)//txtp(jq)
[1114]355          END DO
356       END IF
357    END DO
358
359!
360! Find vector keeping the correspodence between true and total tracers
361!
362    niadv(:)=0
363    iiq=0
364    DO iq=1,nqtot
365       IF(iadv(iq).GE.0) THEN
366          ! True tracer
367          iiq=iiq+1
368          niadv(iiq)=iq
369       ENDIF
370    END DO
371
372
[1454]373    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
374    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
[1114]375    DO iq=1,nqtot
[1454]376       WRITE(lunout,*) iadv(iq),niadv(iq),&
377       ' ',trim(tname(iq)),' ',trim(ttext(iq))
[1114]378    END DO
379
[1279]380!
381! Test for advection schema.
382! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
383!
384    DO iq=1,nqtot
385       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
[1454]386          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
[1279]387          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
388       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
[1454]389          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
[1279]390          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
391       END IF
392    END DO
393
[1114]394!-----------------------------------------------------------------------
395! Finalize :
396!
397    DEALLOCATE(tnom_0, hadv, vadv)
398
[2381]399
[1114]400  END SUBROUTINE infotrac_init
401
402END MODULE infotrac
Note: See TracBrowser for help on using the repository browser.