source: LMDZ5/trunk/libf/dyn3dmem/infotrac.F90 @ 1632

Last change on this file since 1632 was 1632, checked in by Laurent Fairhead, 12 years ago

Import initial du répertoire dyn3dmem

Attention! ceci n'est qu'une version préliminaire du code "basse mémoire":
le code contenu dans ce répertoire est basé sur la r1320 et a donc besoin
d'être mis à jour par rapport à la dynamique parallèle d'aujourd'hui.
Ce code est toutefois mis à disposition pour circonvenir à des problèmes
de mémoire que certaines configurations du modèle pourraient rencontrer.
Dans l'état, il compile et tourne sur vargas et au CCRT


Initial import of dyn3dmem

Warning! this is just a preliminary version of the memory light code:
it is based on r1320 of the code and thus needs to be updated before
it can replace the present dyn3dpar code. It is nevertheless put at your
disposal to circumvent some memory problems some LMDZ configurations may
encounter. In its present state, it will compile and run on vargas and CCRT

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    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=13)               :: 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    INTEGER, EXTERNAL :: lnblnk
68 
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,*) 'Open traceur.def : ok'
103          READ(90,*) nqtrue
104       ELSE
105          WRITE(lunout,*) 'Problem in opening traceur.def'
106          WRITE(lunout,*) 'ATTENTION using defaut values'
107          nqtrue=4 ! Defaut value
108       END IF
109       ! Attention! Only for planet_type=='earth'
110       nbtr=nqtrue-2
111    ELSE
112       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
113       nqtrue=nbtr+2
114    END IF
115
116    IF (nqtrue < 2) THEN
117       WRITE(lunout,*) 'nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
118       CALL abort_gcm('infotrac_init','Not enough tracers',1)
119    END IF
120!
121! Allocate variables depending on nqtrue and nbtr
122!
123    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
124    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
125    conv_flg(:) = 1 ! convection activated for all tracers
126    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
127
128!-----------------------------------------------------------------------
129! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
130!
131!     iadv = 1    schema  transport type "humidite specifique LMD"
132!     iadv = 2    schema   amont
133!     iadv = 14   schema  Van-leer + humidite specifique
134!                            Modif F.Codron
135!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
136!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
137!     iadv = 12   schema  Frederic Hourdin I
138!     iadv = 13   schema  Frederic Hourdin II
139!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
140!     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
141!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
142!     iadv = 20   schema  Slopes
143!     iadv = 30   schema  Prather
144!
145!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
146!                                     iq = 2  pour l'eau liquide
147!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
148!
149!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
150!------------------------------------------------------------------------
151!
152!    Get choice of advection schema from file tracer.def or from INCA
153!---------------------------------------------------------------------
154    IF (type_trac == 'lmdz') THEN
155       IF(ierr.EQ.0) THEN
156          ! Continue to read tracer.def
157          DO iq=1,nqtrue
158             READ(90,999) hadv(iq),vadv(iq),tnom_0(iq)
159          END DO
160          CLOSE(90) 
161       ELSE ! Without tracer.def
162          hadv(1) = 14
163          vadv(1) = 14
164          tnom_0(1) = 'H2Ov'
165          hadv(2) = 10
166          vadv(2) = 10
167          tnom_0(2) = 'H2Ol'
168          hadv(3) = 10
169          vadv(3) = 10
170          tnom_0(3) = 'RN'
171          hadv(4) = 10
172          vadv(4) = 10
173          tnom_0(4) = 'PB'
174       END IF
175       
176       WRITE(lunout,*) 'Valeur de traceur.def :'
177       WRITE(lunout,*) 'nombre de traceurs ',nqtrue
178       DO iq=1,nqtrue
179          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
180       END DO
181
182    ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
183! le module de chimie fournit les noms des traceurs
184! et les schemas d'advection associes.
185     
186#ifdef INCA
187       CALL init_transport( &
188            hadv, &
189            vadv, &
190            conv_flg, &
191            pbl_flg,  &
192            tracnam)
193#endif
194       tnom_0(1)='H2Ov'
195       tnom_0(2)='H2Ol'
196
197       DO iq =3,nqtrue
198          tnom_0(iq)=tracnam(iq-2)
199       END DO
200
201    END IF ! type_trac
202
203!-----------------------------------------------------------------------
204!
205! 3) Verify if advection schema 20 or 30 choosen
206!    Calculate total number of tracers needed: nqtot
207!    Allocate variables depending on total number of tracers
208!-----------------------------------------------------------------------
209    new_iq=0
210    DO iq=1,nqtrue
211       ! Add tracers for certain advection schema
212       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
213          new_iq=new_iq+1  ! no tracers added
214       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
215          new_iq=new_iq+4  ! 3 tracers added
216       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
217          new_iq=new_iq+10 ! 9 tracers added
218       ELSE
219          WRITE(lunout,*) 'This choice of advection schema is not available'
220          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
221       END IF
222    END DO
223   
224    IF (new_iq /= nqtrue) THEN
225       ! The choice of advection schema imposes more tracers
226       ! Assigne total number of tracers
227       nqtot = new_iq
228
229       WRITE(lunout,*) 'The choice of advection schema for one or more tracers'
230       WRITE(lunout,*) 'makes it necessary to add tracers'
231       WRITE(lunout,*) nqtrue,' is the number of true tracers'
232       WRITE(lunout,*) nqtot, ' is the total number of tracers needed'
233
234    ELSE
235       ! The true number of tracers is also the total number
236       nqtot = nqtrue
237    END IF
238
239!
240! Allocate variables with total number of tracers, nqtot
241!
242    ALLOCATE(tname(nqtot), ttext(nqtot))
243    ALLOCATE(iadv(nqtot), niadv(nqtot))
244
245!-----------------------------------------------------------------------
246!
247! 4) Determine iadv, long and short name
248!
249!-----------------------------------------------------------------------
250    new_iq=0
251    DO iq=1,nqtrue
252       new_iq=new_iq+1
253
254       ! Verify choice of advection schema
255       IF (hadv(iq)==vadv(iq)) THEN
256          iadv(new_iq)=hadv(iq)
257       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
258          iadv(new_iq)=11
259       ELSE
260          WRITE(lunout,*)'This choice of advection schema is not available'
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)=str1(1:lnblnk(str1))
268       ELSE
269          ttext(new_iq)=str1(1:lnblnk(str1))//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)=str2(1:lnblnk(str2))//txts(jq)
279             tname(new_iq)=str1(1:lnblnk(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)=str2(1:lnblnk(str2))//txtp(jq)
286             tname(new_iq)=str1(1:lnblnk(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.