source: LMDZ4/trunk/libf/dyn3d/infotrac.F90 @ 1418

Last change on this file since 1418 was 1403, checked in by Laurent Fairhead, 14 years ago

Merged LMDZ4V5.0-dev branch changes r1292:r1399 to trunk.

Validation:
Validation consisted in compiling the HEAD revision of the trunk,
LMDZ4V5.0-dev branch and the merged sources and running different
configurations on local and SX8 machines comparing results.

Local machine: bench configuration, 32x24x11, gfortran

  • IPSLCM5A configuration (comparison between trunk and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent
  • MH07 configuration, new physics package (comparison between LMDZ4V5.0-dev branch and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent

SX8 machine (brodie), 96x95x39 on 4 processors:

  • IPSLCM5A configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent
  • MH07 configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent

Changes to the makegcm and create_make_gcm scripts to take into account
main programs in F90 files


Fusion de la branche LMDZ4V5.0-dev (r1292:r1399) au tronc principal

Validation:
La validation a consisté à compiler la HEAD de le trunk et de la banche
LMDZ4V5.0-dev et les sources fusionnées et de faire tourner le modéle selon
différentes configurations en local et sur SX8 et de comparer les résultats

En local: 32x24x11, config bench/gfortran

  • pour une config IPSLCM5A (comparaison tronc/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux (à part sur RN et Pb)
    • fichiers histoire égaux
  • pour une config nlle physique (MH07) (comparaison LMDZ4v5.0-dev/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux
    • fichiers histoire équivalents

Sur brodie, 96x95x39 sur 4 proc:

  • pour une config IPSLCM5A:
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc
  • pour une config MH07
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc

Changement sur makegcm et create_make-gcm pour pouvoir prendre en compte des
programmes principaux en *F90

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