/[lmdze]/trunk/libf/dyn3d/iniadvtrac.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/iniadvtrac.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 18 - (show annotations)
Thu Aug 7 12:29:13 2008 UTC (15 years, 9 months ago) by guez
File size: 6475 byte(s)
In module "regr_pr", rewrote scanning of horizontal positions as a
single set of loops, using a mask.

Added some "intent" attributes.

In "dynredem0", replaced calls to Fortran 77 interface of NetCDF by
calls to NetCDF95. Removed calls to "nf_redef", regrouped all writing
operations. In "dynredem1", replaced some calls to Fortran 77
interface of NetCDF by calls to Fortran 90 interface.

Renamed variable "nqmax" to "nq_phys".

In "physiq", if "nq >= 5" then "wo" is computed from the
parameterization of "Cariolle".

1 module iniadvtrac_m
2
3 ! From advtrac.h, v 1.1.1.1 2004/05/19 12:53:06
4
5 use dimens_m, only: nqmx
6
7 implicit none
8
9 private nqmx
10
11 INTEGER iadv(nqmx) ! indice schema de transport
12 INTEGER hadv(nqmx) ! indice schema transport horizontal
13 INTEGER vadv(nqmx) ! indice schema transport vertical
14 INTEGER niadv(nqmx) ! equivalent dyn / physique
15 character(len=8) tnom(nqmx) ! nom court du traceur
16 character(len=10) tname(nqmx) ! nom du traceur pour restart
17 character(len=13) ttext(nqmx) ! nom long du traceur pour sorties
18
19 contains
20
21 subroutine iniadvtrac(nq)
22
23 ! From dyn3d/iniadvtrac.F, version 1.3 2005/04/13 08:58:34
24
25 ! Authors : P. Le Van, L. Fairhead, F. Hourdin
26 ! Modification spéciale traceur F. Forget 05/94
27 ! Modification M.-A. Filiberti 02/02 lecture de "traceur.def"
28 ! Modification de l'intégration de "q" (26/04/94)
29
30 integer, intent(out), optional:: nq
31
32 ! Variables local to the procedure:
33
34 character(len=3) descrq(30)
35 character:: txts(3) = (/'x', 'y', 'z'/)
36 character(len=2) txtp(9)
37 character(len=13) str1, str2
38
39 integer iq, iiq, iiiq, ierr, ii, nq_local
40
41 data txtp/'x', 'y', 'z', 'xx', 'xy', 'xz', 'yy', 'yz', 'zz'/
42
43 !-----------------------------------------------------------------------
44
45 print *, "Call sequence information: iniadvtrac"
46
47 ! Initializations:
48 descrq(14)='VLH'
49 descrq(10)='VL1'
50 descrq(11)='VLP'
51 descrq(12)='FH1'
52 descrq(13)='FH2'
53 descrq(16)='PPM'
54 descrq(17)='PPS'
55 descrq(18)='PPP'
56 descrq(20)='SLP'
57 descrq(30)='PRA'
58
59 ! Choix des schemas d'advection pour l'eau et les traceurs
60
61 ! iadv = 1 schema transport type "humidite specifique LMD"
62 ! iadv = 2 schema amont
63 ! iadv = 14 schema Van-leer + humidite specifique
64 ! Modif F.Codron
65 ! iadv = 10 schema Van-leer (retenu pour l'eau vapeur et liquide)
66 ! iadv = 11 schema Van-Leer pour hadv et version PPM (Monotone)
67 ! pour vadv
68 ! iadv = 12 schema Frederic Hourdin I
69 ! iadv = 13 schema Frederic Hourdin II
70 ! iadv = 16 schema PPM Monotone(Collela & Woodward 1984)
71 ! iadv = 17 schema PPM Semi Monotone (overshoots autorisés)
72 ! iadv = 18 schema PPM Positif Defini (overshoots undershoots autorisés)
73 ! iadv = 20 schema Slopes
74 ! iadv = 30 schema Prather
75
76 ! Dans le tableau q(ij, l, iq) : iq = 1 pour l'eau vapeur
77 ! iq = 2 pour l'eau liquide
78 ! Et éventuellement iq = 3, nqmx pour les autres traceurs
79
80 ! iadv(1): choix pour l'eau vap. et iadv(2) : choix pour l'eau liq.
81
82 ! Choix du schema d'advection
83 ! choix par defaut = van leer pour tous les traceurs
84 do iq=1, nqmx
85 iadv(iq)=10
86 str1(1:1)='q'
87 if (nqmx.le.99) then
88 WRITE(str1(2:3), '(i2.2)') iq
89 else
90 WRITE(str1(2:4), '(i3.3)') iq
91 endif
92 tnom(iq)=str1
93 tname(iq)=tnom(iq)
94 str2=tnom(iq)
95 ttext(iq) = trim(str2) // descrq(iadv(iq))
96 end do
97
98 ! Choix du schema pour l'advection dans fichier "traceur.def"
99
100 open(unit=90, file='traceur.def', form='formatted', status='old', &
101 iostat=ierr)
102 if (ierr == 0) then
103 print *, 'Ouverture de "traceur.def" ok'
104 read(unit=90, fmt=*) nq_local
105 print *, 'nombre de traceurs ', nq_local
106 if (nq_local > nqmx) then
107 print *, 'nombre de traceurs trop important'
108 print *, 'verifier traceur.def'
109 stop 1
110 endif
111
112 do iq=1, nq_local
113 read(90, 999) hadv(iq), vadv(iq), tnom(iq)
114 end do
115 close(90)
116 PRINT *, 'lecture de traceur.def :'
117 do iq=1, nq_local
118 write(*, *) hadv(iq), vadv(iq), tnom(iq)
119 end do
120 else
121 print *, 'Problème à l''ouverture de "traceur.def"'
122 print *, 'Attention : on prend des valeurs par défaut.'
123 nq_local = 4
124 hadv(1) = 14
125 vadv(1) = 14
126 tnom(1) = 'H2Ov'
127 hadv(2) = 10
128 vadv(2) = 10
129 tnom(2) = 'H2Ol'
130 hadv(3) = 10
131 vadv(3) = 10
132 tnom(3) = 'RN'
133 hadv(4) = 10
134 vadv(4) = 10
135 tnom(4) = 'PB'
136 ENDIF
137 PRINT *, 'Valeur de traceur.def :'
138 do iq=1, nq_local
139 write(*, *) hadv(iq), vadv(iq), tnom(iq)
140 end do
141
142 ! À partir du nom court du traceur et du schéma d'advection, on
143 ! détemine le nom long :
144 iiq=0
145 ii=0
146 do iq=1, nq_local
147 iiq=iiq+1
148 if (hadv(iq) /= vadv(iq)) then
149 if (hadv(iq) == 10.and.vadv(iq) == 16) then
150 iadv(iiq)=11
151 else
152 print *, 'le choix des schemas d''advection H et V'
153 print *, 'est non disponible actuellement'
154 stop
155 endif
156 else
157 iadv(iiq)=hadv(iq)
158 endif
159 ! verification nombre de traceurs
160 if (iadv(iiq).lt.20) then
161 ii=ii+1
162 elseif (iadv(iiq) == 20) then
163 ii=ii+4
164 elseif (iadv(iiq) == 30) then
165 ii=ii+10
166 endif
167
168 str1=tnom(iq)
169 tname(iiq)=tnom(iq)
170 IF (iadv(iiq) == 0) THEN
171 ttext(iiq)=trim(str1)
172 ELSE
173 ttext(iiq)=trim(str1)//descrq(iadv(iiq))
174 endif
175 str2=ttext(iiq)
176 ! schemas tenant compte des moments d'ordre superieur.
177 if (iadv(iiq) == 20) then
178 do iiiq=1, 3
179 iiq=iiq+1
180 iadv(iiq)=-20
181 ttext(iiq)=trim(str2)//txts(iiiq)
182 tname(iiq)=trim(str1)//txts(iiiq)
183 enddo
184 elseif (iadv(iiq) == 30) then
185 do iiiq=1, 9
186 iiq=iiq+1
187 iadv(iiq)=-30
188 ttext(iiq)=trim(str2)//txtp(iiiq)
189 tname(iiq)=trim(str1)//txtp(iiiq)
190 enddo
191 endif
192 end do
193 if (ii /= nqmx) then
194 print *, 'WARNING'
195 print *, 'le nombre de traceurs et de moments eventuels'
196 print *, 'est inferieur a nqmx '
197 endif
198 if (iiq > nqmx) then
199 print *, 'le choix des schemas est incompatible avec '
200 print *, 'la dimension nqmx (nombre de traceurs)'
201 print *, 'verifier traceur.def ou la namelist INCA'
202 print *, 'ou recompiler avec plus de traceurs'
203 stop
204 endif
205 iiq=0
206 do iq=1, nqmx
207 if (iadv(iq).ge.0) then
208 iiq=iiq+1
209 niadv(iiq)=iq
210 endif
211 end do
212 if (present(nq)) nq = nq_local
213
214 999 format (i2, 1x, i2, 1x, a8)
215
216 END subroutine iniadvtrac
217
218 end module iniadvtrac_m

  ViewVC Help
Powered by ViewVC 1.1.21