source: LMDZ4/trunk/libf/dyn3dpar/iniadvtrac.F @ 1014

Last change on this file since 1014 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.2 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"
30
31c   local
32      character*3 descrq(30)
33      character*1 txts(3)
34      character*2 txtp(9)
35      character*13 str1,str2,str3
36
37      integer nq,iq,iiq,iiiq,ierr,ii
38      integer lnblnk
39      external lnblnk
40
41      data txts/'x','y','z'/
42      data txtp/'x','y','z','xx','xy','xz','yy','yz','zz'/
43
44c-----------------------------------------------------------------------
45c   Initialisations:
46c   ----------------
47      descrq(14)='VLH'
48      descrq(10)='VL1'
49      descrq(11)='VLP'
50      descrq(12)='FH1'
51      descrq(13)='FH2'
52      descrq(16)='PPM'
53      descrq(17)='PPS'
54      descrq(18)='PPP'
55      descrq(20)='SLP'
56      descrq(30)='PRA'
57
58      IF (config_inca /= 'none') THEN
59#ifdef INCA
60         CALL init_transport(
61     $        hadv_flg,
62     $        vadv_flg,
63     $        conv_flg,
64     $        pbl_flg,
65     $        tracnam)
66#endif
67      END IF
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
113      IF (config_inca /= 'none') THEN
114C le module de chimie fournit les noms des traceurs
115C et les schemas d'advection associes.
116         tnom(1)='H2Ov'
117         tnom(2)='H2Ol'
118         nq=nbtrac+2
119     
120       if (nq.gt.nqmx) then
121       print*,'nombre de traceurs incompatible INCA/LMDZT', nq, nbtrac
122       stop
123       endif
124      do iq =3,nq
125      tnom(iq)=tracnam(iq-2)
126      end do
127      do iq =1,nq
128      hadv(iq)= hadv_flg(iq)
129      vadv(iq)= vadv_flg(iq)
130      end do
131      ELSE  ! config_inca=none
132         print*,'ouverture de traceur.def'
133         open(90,file='traceur.def',form='formatted',status='old',
134     s        iostat=ierr)
135      if(ierr.eq.0) then
136        print*,'ouverture de traceur.def ok'
137        read(90,*) nq
138        print*,'nombre de traceurs ',nq
139        if (nq.gt.nqmx) then
140          print*,'nombre de traceurs trop important'
141          print*,'verifier traceur.def'
142          stop
143        endif
144C
145        do iq=1,nq
146          read(90,999) hadv(iq),vadv(iq),tnom(iq)
147        end do
148        close(90) 
149        PRINT*,'lecture de traceur.def :'   
150        do iq=1,nq
151          write(*,*) hadv(iq),vadv(iq),tnom(iq)
152        end do       
153      else
154        print*,'pb ouverture traceur.def'
155        print*,'ATTENTION on prend des valeurs par defaut'
156        nq = 4
157        hadv(1) = 14
158        vadv(1) = 14
159        tnom(1) = 'H2Ov'
160        hadv(2) = 10
161        vadv(2) = 10
162        tnom(2) = 'H2Ol'
163        hadv(3) = 10
164        vadv(3) = 10
165        tnom(3) = 'RN'
166        hadv(4) = 10
167        vadv(4) = 10
168        tnom(4) = 'PB'
169      ENDIF
170      PRINT*,'Valeur de traceur.def :'
171      do iq=1,nq
172        write(*,*) hadv(iq),vadv(iq),tnom(iq)
173      end do       
174
175      END IF ! config_inca
176
177c a partir du nom court du traceur et du schema d'advection au detemine le nom long.
178        iiq=0
179        ii=0
180        do iq=1,nq
181         iiq=iiq+1
182         if (hadv(iq).ne.vadv(iq)) then
183           if (hadv(iq).eq.10.and.vadv(iq).eq.16) then
184             iadv(iiq)=11
185           else
186             print*,'le choix des schemas d''advection H et V'
187             print*, 'est non disponible actuellement'
188             stop
189           endif
190         else
191          iadv(iiq)=hadv(iq)
192         endif
193c verification nombre de traceurs
194          if (iadv(iiq).lt.20) then
195             ii=ii+1
196          elseif (iadv(iiq).eq.20) then
197             ii=ii+4
198          elseif (iadv(iiq).eq.30) then
199             ii=ii+10
200          endif
201 
202         str1=tnom(iq)
203         tname(iiq)=tnom(iq)
204         IF (iadv(iiq).eq.0) THEN
205           ttext(iiq)=str1(1:lnblnk(str1))
206         ELSE
207           ttext(iiq)=str1(1:lnblnk(str1))//descrq(iadv(iiq))
208         ENDIF
209         str2=ttext(iiq)
210c   schemas tenant compte des moments d'ordre superieur.
211          if (iadv(iiq).eq.20) then
212             do iiiq=1,3
213               iiq=iiq+1
214               iadv(iiq)=-20
215               ttext(iiq)=str2(1:lnblnk(str2))//txts(iiiq)
216               tname(iiq)=str1(1:lnblnk(str1))//txts(iiiq)
217              enddo
218            elseif (iadv(iiq).eq.30) then
219              do iiiq=1,9
220               iiq=iiq+1
221               iadv(iiq)=-30
222               ttext(iiq)=str2(1:lnblnk(str2))//txtp(iiiq)
223               tname(iiq)=str1(1:lnblnk(str1))//txtp(iiiq)
224              enddo
225           endif
226        end do
227       if(ii.ne.nqmx) then
228       print*,'WARNING'
229       print*,'le nombre de traceurs et de moments eventuels'
230       print*,'est inferieur a nqmx '
231       endif
232       if (iiq.gt.nqmx) then
233       print*,'le choix des schemas est incompatible avec '
234       print*,'la dimension nqmx (nombre de traceurs)'
235       print*,'verifier traceur.def ou la namelist INCA'
236       print*,'ou recompiler avec plus de traceurs'
237       stop
238       endif
239      iiq=0
240      do iq=1,nqmx
241         if(iadv(iq).ge.0) then
242             iiq=iiq+1
243             niadv(iiq)=iq
244         endif
245      end do
246      return
247999   format (i2,1x,i2,1x,a8)
248      END
Note: See TracBrowser for help on using the repository browser.