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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 38 - (show annotations)
Thu Jan 6 17:52:19 2011 UTC (13 years, 4 months ago) by guez
File size: 6426 byte(s)
Extracted ASCII art from "inigeom" into a separate text file in the
documentation.

"test_disvert" now creates a separate file for layer thicknesses.

Moved variables from module "yomcst" to module "suphec_m" because this
is where those variables are defined. Kept in "yomcst" only parameters
of Earth orbit. Gave the attribute "parameter" to some variables of
module "suphec_m".

Variables of module "yoethf" were defined in procedure "suphec". Moved
these definitions to a new procedure "yoethf" in module "yoethf_m".

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

  ViewVC Help
Powered by ViewVC 1.1.21