13 CHARACTER(len=20),
ALLOCATABLE,
DIMENSION(:),
SAVE :: tname
14 CHARACTER(len=23),
ALLOCATABLE,
DIMENSION(:),
SAVE :: ttext
17 INTEGER,
ALLOCATABLE,
DIMENSION(:),
SAVE :: iadv
21 INTEGER,
ALLOCATABLE,
DIMENSION(:),
SAVE :: niadv
24 INTEGER,
ALLOCATABLE,
DIMENSION(:),
SAVE :: conv_flg
26 INTEGER,
ALLOCATABLE,
DIMENSION(:),
SAVE :: pbl_flg
28 CHARACTER(len=4),
SAVE :: type_trac
35 USE chem_rep
, ONLY : Init_chem_rep_trac
54 include
"dimensions.h"
58 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: hadv
59 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: vadv
61 CHARACTER(len=15),
ALLOCATABLE,
DIMENSION(:) :: tnom_0
62 CHARACTER(len=8),
ALLOCATABLE,
DIMENSION(:) :: tracnam
63 CHARACTER(len=3),
DIMENSION(30) :: descrq
64 CHARACTER(len=1),
DIMENSION(3) :: txts
65 CHARACTER(len=2),
DIMENSION(9) :: txtp
66 CHARACTER(len=23) :: str1,str2
69 INTEGER :: iq, new_iq, iiq, jq, ierr
71 character(len=*),
parameter :: modname=
"infotrac_init"
76 txtp=(/
'x ',
'y ',
'z ',
'xx',
'xy',
'xz',
'yy',
'yz',
'zz'/)
91 IF (type_trac==
'inca')
THEN
92 WRITE(
lunout,*)
'You have choosen to couple with INCA chemestry model : type_trac=', &
93 type_trac,
' config_inca=',config_inca
94 IF (config_inca/=
'aero' .AND. config_inca/=
'chem')
THEN
95 WRITE(
lunout,*)
'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
96 CALL
abort_gcm(
'infotrac_init',
'Incoherence between type_trac and config_inca',1)
99 WRITE(
lunout,*)
'To run this option you must add cpp key INCA and compile with INCA code'
100 CALL
abort_gcm(
'infotrac_init',
'You must compile with cpp key INCA',1)
102 ELSE IF (type_trac==
'repr')
THEN
103 WRITE(
lunout,*)
'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
105 WRITE(
lunout,*)
'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
106 CALL
abort_gcm(
'infotrac_init',
'You must compile with cpp key REPROBUS',1)
108 ELSE IF (type_trac ==
'lmdz')
THEN
109 WRITE(
lunout,*)
'Tracers are treated in LMDZ only : type_trac=', type_trac
111 WRITE(
lunout,*)
'type_trac=',type_trac,
' not possible. Model stops'
112 CALL
abort_gcm(
'infotrac_init',
'bad parameter',1)
117 IF (type_trac/=
'inca' .AND. config_inca/=
'none')
THEN
118 WRITE(
lunout,*)
'config_inca will now be changed to none as you do not couple with INCA model'
129 IF (type_trac ==
'lmdz' .OR. type_trac ==
'repr')
THEN
130 OPEN(90,file=
'traceur.def',form=
'formatted',status=
'old', iostat=ierr)
132 WRITE(
lunout,*) trim(modname),
': Open traceur.def : ok'
135 WRITE(
lunout,*) trim(modname),
': Problem in opening traceur.def'
136 WRITE(
lunout,*) trim(modname),
': WARNING using defaut values'
137 if (planet_type==
'earth')
then
143 if ( planet_type==
'earth')
then
156 IF ((planet_type==
"earth").and.(nqtrue < 2))
THEN
157 WRITE(
lunout,*) trim(modname),
': nqtrue=',nqtrue,
' is not allowded. 2 tracers is the minimum'
158 CALL
abort_gcm(
'infotrac_init',
'Not enough tracers',1)
162 IF (type_trac ==
'repr')
THEN
164 CALL init_chem_rep_trac(nbtr)
171 ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
172 ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
202 IF (type_trac ==
'lmdz' .OR. type_trac ==
'repr')
THEN
206 READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
210 if (planet_type==
"earth")
then
231 WRITE(
lunout,*) trim(modname),
': Valeur de traceur.def :'
232 WRITE(
lunout,*) trim(modname),
': nombre de traceurs ',nqtrue
234 WRITE(
lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
242 CALL init_transport( &
253 tnom_0(iq)=tracnam(iq-2)
267 IF (hadv(iq)<20 .AND. vadv(iq)<20 )
THEN
269 ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 )
THEN
271 ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 )
THEN
274 WRITE(
lunout,*) trim(modname),
': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
275 CALL
abort_gcm(
'infotrac_init',
'Bad choice of advection schema - 1',1)
279 IF (new_iq /= nqtrue)
THEN
284 WRITE(
lunout,*) trim(modname),
': The choice of advection schema for one or more tracers'
285 WRITE(
lunout,*)
'makes it necessary to add tracers'
286 WRITE(
lunout,*) trim(modname)//
': ',nqtrue,
' is the number of true tracers'
287 WRITE(
lunout,*) trim(modname)//
': ',nqtot,
' is the total number of tracers needed'
297 ALLOCATE(tname(nqtot), ttext(nqtot))
298 ALLOCATE(iadv(nqtot), niadv(nqtot))
310 IF (hadv(iq)==vadv(iq))
THEN
311 iadv(new_iq)=hadv(iq)
312 ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16)
THEN
315 WRITE(
lunout,*)trim(modname),
': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
317 CALL
abort_gcm(
'infotrac_init',
'Bad choice of advection schema - 2',1)
321 tname(new_iq)= tnom_0(iq)
322 IF (iadv(new_iq)==0)
THEN
323 ttext(new_iq)=trim(str1)
325 ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
330 IF (iadv(new_iq)==20)
THEN
334 ttext(new_iq)=trim(str2)//txts(jq)
335 tname(new_iq)=trim(str1)//txts(jq)
337 ELSE IF (iadv(new_iq)==30)
THEN
341 ttext(new_iq)=trim(str2)//txtp(jq)
342 tname(new_iq)=trim(str1)//txtp(jq)
353 IF(iadv(iq).GE.0)
THEN
361 WRITE(
lunout,*) trim(modname),
': Information stored in infotrac :'
362 WRITE(
lunout,*) trim(modname),
': iadv niadv tname ttext :'
364 WRITE(
lunout,*) iadv(iq),niadv(iq),&
365 ' ',trim(tname(iq)),
' ',trim(ttext(iq))
373 IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0)
THEN
374 WRITE(
lunout,*)trim(modname),
' STOP : The option iadv=',iadv(iq),
' is not tested in this version of LMDZ'
375 CALL
abort_gcm(
'infotrac_init',
'In this version only iadv=10 and iadv=14 is tested!',1)
376 ELSE IF (iadv(iq)==14 .AND. iq/=1)
THEN
377 WRITE(
lunout,*)trim(modname),
'STOP : The option iadv=',iadv(iq),
' is not tested in this version of LMDZ'
378 CALL
abort_gcm(
'infotrac_init',
'In this version iadv=14 is only permitted for water vapour!',1)
385 DEALLOCATE(tnom_0, hadv, vadv)