source: LMDZ4/trunk/libf/dyn3d/iniadvtrac.F @ 962

Last change on this file since 962 was 960, checked in by lsce, 16 years ago
  • Ajoute du parametre config_inca dans conf_gcm.F config_inca='none'(sans INCA, par defaut) config_inca='chem'(avec INCA config chemie) config_inca='aero'(avec INCA config aerosol)
  • Menage parmis les cles CPP INCA
  • Enleve le calcul d'omega dans calfis.F et active le calcul correspondant dans advtrac.F(avant uniquement pour INCA).

JG

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.4 KB
Line 
1!
2! $Header$
3!
4c
5c
6      subroutine iniadvtrac(nq)
7      USE ioipsl
8      IMPLICIT NONE
9c=======================================================================
10c
11c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
12c   -------
13c   Modif special traceur F.Forget 05/94
14c   Modif M-A Filiberti 02/02 lecture de traceur.def
15c
16c   Objet:
17c   ------
18c
19c   GCM LMD nouvelle grille
20c
21c=======================================================================
22c   ... modification de l'integration de q ( 26/04/94 ) ....
23c-----------------------------------------------------------------------
24c   Declarations:
25c   -------------
26C
27#include "dimensions.h"
28#include "advtrac.h"
29#include "control.h"
30c   local
31      character*3 descrq(30)
32      character*1 txts(3)
33      character*2 txtp(9)
34      character*13 str1,str2,str3
35
36      integer nq,iq,iiq,iiiq,ierr,ii
37      integer lnblnk
38      external lnblnk
39
40      data txts/'x','y','z'/
41      data txtp/'x','y','z','xx','xy','xz','yy','yz','zz'/
42
43c-----------------------------------------------------------------------
44c   Initialisations:
45c   ----------------
46      descrq(14)='VLH'
47      descrq(10)='VL1'
48      descrq(11)='VLP'
49      descrq(12)='FH1'
50      descrq(13)='FH2'
51      descrq(16)='PPM'
52      descrq(17)='PPS'
53      descrq(18)='PPP'
54      descrq(20)='SLP'
55      descrq(30)='PRA'
56
57      IF (config_inca /= 'none') THEN
58#ifdef INCA
59         CALL init_transport(
60     $        hadv_flg,
61     $        vadv_flg,
62     $        conv_flg,
63     $        pbl_flg,
64     $        tracnam)
65#endif
66      END IF
67
68c-----------------------------------------------------------------------
69c        Choix  des schemas d'advection pour l'eau et les traceurs
70c
71c     iadv = 1    schema  transport type "humidite specifique LMD"
72c     iadv = 2    schema   amont
73c     iadv = 14    schema  Van-leer + humidite specifique
74c                            Modif F.Codron
75c     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
76c     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
77c     iadv = 12   schema  Frederic Hourdin I
78c     iadv = 13   schema  Frederic Hourdin II
79c     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
80c     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
81c     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
82c     iadv = 20   schema  Slopes
83c     iadv = 30   schema  Prather
84c
85c        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
86c                                     iq = 2  pour l'eau liquide
87c        Et eventuellement            iq = 3,nqmx pour les autres traceurs
88c
89c        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
90C------------------------------------------------------------------------
91c     Choix du schema d'advection
92c------------------------------------------------------------------
93c choix par defaut = van leer pour tous les traceurs
94      do iq=1,nqmx
95       iadv(iq)=10
96       str1(1:1)='q'
97       if (nqmx.le.99) then
98       WRITE(str1(2:3),'(i2.2)') iq
99       else
100       WRITE(str1(2:4),'(i3.3)') iq
101       endif
102       tnom(iq)=str1
103       tname(iq)=tnom(iq)
104       str2=tnom(iq)
105       ttext(iq)=str2(1:lnblnk(str2))//descrq(iadv(iq))
106      end do
107      nq=nqmx
108c------------------------------------------------------------------
109c     Choix du schema pour l'advection
110c    dans fichier traceur.def
111c------------------------------------------------------------------
112      IF (config_inca == 'none') THEN
113         print*,'ouverture de traceur.def'
114         open(90,file='traceur.def',form='formatted',status='old',
115     s        iostat=ierr)
116         if(ierr.eq.0) then
117            print*,'ouverture de traceur.def ok'
118            read(90,*) nq
119            print*,'nombre de traceurs ',nq
120            if (nq.gt.nqmx) then
121               print*,'nombre de traceurs trop important'
122               print*,'verifier traceur.def'
123               stop
124            endif
125C     
126            do iq=1,nq
127               read(90,999) hadv(iq),vadv(iq),tnom(iq)
128            end do
129            close(90) 
130            PRINT*,'lecture de traceur.def :'   
131            do iq=1,nq
132               write(*,*) hadv(iq),vadv(iq),tnom(iq)
133            end do       
134         else
135            print*,'pb ouverture traceur.def'
136            print*,'ATTENTION on prend des valeurs par defaut'
137            nq = 4
138            hadv(1) = 14
139            vadv(1) = 14
140            tnom(1) = 'H2Ov'
141            hadv(2) = 10
142            vadv(2) = 10
143            tnom(2) = 'H2Ol'
144            hadv(3) = 10
145            vadv(3) = 10
146            tnom(3) = 'RN'
147            hadv(4) = 10
148            vadv(4) = 10
149            tnom(4) = 'PB'
150         ENDIF
151         PRINT*,'Valeur de traceur.def :'
152         do iq=1,nq
153            write(*,*) hadv(iq),vadv(iq),tnom(iq)
154         end do       
155      ELSE  ! config_inca='aero' ou 'chem'
156C le module de chimie fournit les noms des traceurs
157C et les schemas d'advection associes.
158         tnom(1)='H2Ov'
159         tnom(2)='H2Ol'
160         nq=nbtrac+2
161         if (nq.gt.nqmx) then
162            print*,'nombre de traceurs incompatible INCA/LMDZT'
163            stop
164         endif
165         do iq =3,nq
166            tnom(iq)=tracnam(iq-2)
167         end do
168         do iq =1,nq
169            hadv(iq)= hadv_flg(iq)
170            vadv(iq)= vadv_flg(iq)
171         end do
172      END IF ! config_inca
173
174c a partir du nom court du traceur et du schema d'advection au detemine le nom long.
175        iiq=0
176        ii=0
177        do iq=1,nq
178         iiq=iiq+1
179         if (hadv(iq).ne.vadv(iq)) then
180           if (hadv(iq).eq.10.and.vadv(iq).eq.16) then
181             iadv(iiq)=11
182           else
183             print*,'le choix des schemas d''advection H et V'
184             print*, 'est non disponible actuellement'
185             stop
186           endif
187         else
188          iadv(iiq)=hadv(iq)
189         endif
190c verification nombre de traceurs
191          if (iadv(iiq).lt.20) then
192             ii=ii+1
193          elseif (iadv(iiq).eq.20) then
194             ii=ii+4
195          elseif (iadv(iiq).eq.30) then
196             ii=ii+10
197          endif
198 
199         str1=tnom(iq)
200         tname(iiq)=tnom(iq)
201         IF (iadv(iiq).eq.0) THEN
202           ttext(iiq)=str1(1:lnblnk(str1))
203         ELSE
204           ttext(iiq)=str1(1:lnblnk(str1))//descrq(iadv(iiq))
205         endif
206         str2=ttext(iiq)
207c   schemas tenant compte des moments d'ordre superieur.
208          if (iadv(iiq).eq.20) then
209             do iiiq=1,3
210               iiq=iiq+1
211               iadv(iiq)=-20
212               ttext(iiq)=str2(1:lnblnk(str2))//txts(iiiq)
213               tname(iiq)=str1(1:lnblnk(str1))//txts(iiiq)
214              enddo
215            elseif (iadv(iiq).eq.30) then
216              do iiiq=1,9
217               iiq=iiq+1
218               iadv(iiq)=-30
219               ttext(iiq)=str2(1:lnblnk(str2))//txtp(iiiq)
220               tname(iiq)=str1(1:lnblnk(str1))//txtp(iiiq)
221              enddo
222           endif
223        end do
224       if(ii.ne.nqmx) then
225       print*,'WARNING'
226       print*,'le nombre de traceurs et de moments eventuels'
227       print*,'est inferieur a nqmx '
228       endif
229       if (iiq.gt.nqmx) then
230       print*,'le choix des schemas est incompatible avec '
231       print*,'la dimension nqmx (nombre de traceurs)'
232       print*,'verifier traceur.def ou la namelist INCA'
233       print*,'ou recompiler avec plus de traceurs'
234       stop
235       endif
236      iiq=0
237      do iq=1,nqmx
238         if(iadv(iq).ge.0) then
239             iiq=iiq+1
240             niadv(iiq)=iq
241         endif
242      end do
243      return
244999   format (i2,1x,i2,1x,a8)
245      END
Note: See TracBrowser for help on using the repository browser.