source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/aeronomars/inichim_readcallphys.F @ 1242

Last change on this file since 1242 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 12.2 KB
Line 
1      SUBROUTINE inichim_readcallphys
2      IMPLICIT NONE
3c
4c=======================================================================
5c
6c   subject:
7c   --------
8c
9c   Initialisation for the physical parametrisations of the LMD
10c   martian atmospheric general circulation modele.
11c
12c   author: Frederic Hourdin 15 / 10 /93
13c   -------
14c   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
15c
16c
17c   arguments:
18c   ----------
19c
20c   input:
21c   ------
22c
23c    ngrid                 Size of the horizontal grid.
24c                          All internal loops are performed on that grid.
25c    nlayer                Number of vertical layers.
26c    pdayref               Day of reference for the simulation
27c    firstcall             True at the first call
28c    lastcall              True at the last call
29c    pday                  Number of days counted from the North. Spring
30c                          equinoxe.
31c
32c=======================================================================
33c
34c-----------------------------------------------------------------------
35c   declarations:
36c   -------------
37 
38#include "dimensions.h"
39#include "dimphys.h"
40#include "planete.h"
41#include "comcstfi.h"
42#include "comsaison.h"
43#include "comdiurn.h"
44#include "comgeomfi.h"
45#include "callkeys.h"
46#include "surfdat.h"
47
48      character*12 ch1
49      integer ierr
50      logical chem, h2o
51
52
53c --------------------------------------------------------------
54c  Reading the "callphys.def" file controlling some key options
55c --------------------------------------------------------------
56
57      OPEN(99,file='callphys.def',status='old',form='formatted'
58     .     ,iostat=ierr)
59      IF(ierr.EQ.0) THEN
60         PRINT*
61         PRINT*
62         PRINT*,'--------------------------------------------'
63         PRINT*,' Parametres pour la physique (callphys.def)'
64         PRINT*,'--------------------------------------------'
65
66         READ(99,*)
67         READ(99,*)
68
69         READ(99,fmt='(a)') ch1
70         READ(99,*) tracer
71         WRITE(*,8000) ch1,tracer
72
73         READ(99,fmt='(a)') ch1
74         READ(99,'(l1)') diurnal
75         WRITE(*,8000) ch1,diurnal
76
77         READ(99,fmt='(a)') ch1
78         READ(99,'(l1)') season
79         WRITE(*,8000) ch1,season
80
81         READ(99,fmt='(a)') ch1
82         READ(99,'(l1)') lwrite
83         WRITE(*,8000) ch1,lwrite
84
85         READ(99,fmt='(a)') ch1
86         READ(99,'(l1)') callstats
87         WRITE(*,8000) ch1,callstats
88
89         READ(99,fmt='(a)') ch1
90         READ(99,'(l1)') calleofdump
91         WRITE(*,8000) ch1,calleofdump
92
93         READ(99,*)
94         READ(99,*)
95
96         READ(99,fmt='(a)') ch1
97         READ(99,*,iostat=ierr) iaervar
98         if(ierr.ne.0) stop'Can t read iaervar in callphys.def (old?)'
99         WRITE(*,8001) ch1,iaervar
100
101         READ(99,fmt='(a)') ch1
102         READ(99,*) iddist
103         WRITE(*,8001) ch1,iddist
104
105         READ(99,fmt='(a)') ch1
106         READ(99,*) topdustref
107         WRITE(*,8002) ch1,topdustref
108
109         READ(99,*)
110         READ(99,*)
111
112         READ(99,fmt='(a)') ch1
113         READ(99,'(l1)') callrad
114         WRITE(*,8000) ch1,callrad
115
116         READ(99,fmt='(a)') ch1
117         READ(99,'(l1)') callnlte
118         WRITE(*,8000) ch1,callnlte
119         
120         READ(99,fmt='(a)') ch1
121         READ(99,'(l1)') callnirco2
122         WRITE(*,8000) ch1,callnirco2
123
124         READ(99,fmt='(a)') ch1
125         READ(99,'(l1)') calldifv
126         WRITE(*,8000) ch1,calldifv
127
128         READ(99,fmt='(a)') ch1
129         READ(99,'(l1)') calladj
130         WRITE(*,8000) ch1,calladj
131
132         READ(99,fmt='(a)') ch1
133         READ(99,'(l1)') callcond
134         WRITE(*,8000) ch1,callcond
135
136         READ(99,fmt='(a)') ch1
137         READ(99,'(l1)') callsoil
138         WRITE(*,8000) ch1,callsoil
139
140         READ(99,fmt='(a)') ch1
141         READ(99,'(l1)') calllott
142         WRITE(*,8000) ch1,calllott
143
144         READ(99,*)
145         READ(99,*)
146
147         READ(99,fmt='(a)') ch1
148         READ(99,*) iradia
149         WRITE(*,8001) ch1,iradia
150
151         READ(99,fmt='(a)') ch1
152         READ(99,'(l1)') callg2d
153         WRITE(*,8000) ch1,callg2d
154
155         READ(99,fmt='(a)') ch1
156         READ(99,*) rayleigh
157         WRITE(*,8000) ch1,rayleigh
158
159         READ(99,*)
160         READ(99,*)
161
162c TRACERS:
163
164         READ(99,fmt='(a)') ch1
165         READ(99,*) dustbin
166         WRITE(*,8001) ch1,dustbin
167
168         READ(99,fmt='(a)') ch1
169         READ(99,*) active
170         WRITE(*,8000) ch1,active
171
172c Test of incompatibility:
173c if active is used, then dustbin should be > 0
174
175         if (active.and.(dustbin.lt.1)) then
176           print*,'if active is used, then dustbin should > 0'
177           stop
178         endif
179
180         READ(99,fmt='(a)') ch1
181         READ(99,*) doubleq
182         WRITE(*,8000) ch1,doubleq
183
184c Test of incompatibility:
185c if doubleq is used, then dustbin should be 1
186
187         if (doubleq.and.(dustbin.ne.1)) then
188           print*,'if doubleq is used, then dustbin should be 1'
189           stop
190         endif
191
192         READ(99,fmt='(a)') ch1
193         READ(99,*) lifting
194         WRITE(*,8000) ch1,lifting
195
196c Test of incompatibility:
197c if lifting is used, then dustbin should be > 0
198
199         if (lifting.and.(dustbin.lt.1)) then
200           print*,'if lifting is used, then dustbin should > 0'
201           stop
202         endif
203
204         READ(99,fmt='(a)') ch1
205         READ(99,*) callddevil
206         WRITE(*,8000) ch1,callddevil
207
208c Test of incompatibility:
209c if dustdevil is used, then dustbin should be > 0
210
211         if (callddevil.and.(dustbin.lt.1)) then
212           print*,'if dustdevil is used, then dustbin should > 0'
213           stop
214         endif
215
216         READ(99,fmt='(a)') ch1
217         READ(99,*) scavenging
218         WRITE(*,8000) ch1,scavenging
219
220c Test of incompatibility:
221c if scavenging is used, then dustbin should be > 0
222
223         if (scavenging.and.(dustbin.lt.1)) then
224           print*,'if scavenging is used, then dustbin should > 0'
225           stop
226         endif
227
228         READ(99,fmt='(a)') ch1
229         READ(99,*) sedimentation
230         WRITE(*,8000) ch1,sedimentation
231
232         READ(99,fmt='(a)') ch1
233         READ(99,*) iceparty
234         WRITE(*,8000) ch1,iceparty
235
236         READ(99,fmt='(a)') ch1
237         READ(99,*) activice
238         WRITE(*,8000) ch1,activice
239
240c Test of incompatibility:
241c if activice is used, then iceparty should be used too
242
243         if (activice.and..not.iceparty) then
244           print*,'if activice is used, iceparty should be used too'
245           stop
246         endif
247
248         READ(99,fmt='(a)') ch1
249         READ(99,*) water
250         WRITE(*,8000) ch1,water
251
252c Test of incompatibility:
253c if iceparty is used, then water should be used too
254
255         if (iceparty.and..not.water) then
256           print*,'if iceparty is used, then water should be used too'
257           stop
258         endif
259
260         READ(99,fmt='(a)') ch1
261         READ(99,*) caps
262         WRITE(*,8000) ch1,caps
263
264         READ(99,fmt='(a)') ch1
265         READ(99,*) photochem
266         WRITE(*,8000) ch1,photochem
267
268         READ(99,*)
269         READ(99,*)
270
271c THERMOSPHERE
272
273         READ(99,fmt='(a)') ch1
274         READ(99,'(l1)') callthermos
275         WRITE(*,8000) ch1,callthermos
276
277         READ(99,fmt='(a)') ch1
278         READ(99,'(l1)') thermoswater
279         WRITE(*,8000) ch1,thermoswater
280
281         READ(99,fmt='(a)') ch1
282         READ(99,'(l1)') callconduct
283         WRITE(*,8000) ch1,callconduct
284
285         READ(99,fmt='(a)') ch1
286         READ(99,'(l1)') calleuv
287         WRITE(*,8000) ch1,calleuv
288
289         READ(99,fmt='(a)') ch1
290         READ(99,'(l1)') callmolvis
291         WRITE(*,8000) ch1,callmolvis
292
293         READ(99,fmt='(a)') ch1
294         READ(99,'(l1)') callmoldiff
295         WRITE(*,8000) ch1,callmoldiff
296
297         READ(99,fmt='(a)') ch1
298         READ(99,'(l1)') thermochem
299         WRITE(*,8000) ch1,thermochem
300
301         READ(99,fmt='(a)') ch1
302         READ(99,*) solarcondate
303         WRITE(*,*) ch1,solarcondate
304
305c Test of incompatibility:
306c if photochem is used, then water should be used too
307
308         if (photochem.and..not.water) then
309           print*,'if photochem is used, water should be used too'
310           stop
311         endif
312
313c if callthermos is used, then thermoswater should be used too
314c (if water not used already)
315
316         if (callthermos .and. .not.water) then
317           if (callthermos .and. .not.thermoswater) then
318             print*,'if callthermos is used, water or thermoswater
319     &               should be used too'
320             stop
321           endif
322         endif
323
324         PRINT*,'--------------------------------------------'
325         PRINT*
326         PRINT*
327      ELSE
328         write(*,*)
329         write(*,*) 'Cannot read file callphys.def. Is it here ?'
330         stop
331      ENDIF
332      CLOSE(99)
333
334      pi=2.*asin(1.)
335
336c     managing the tracers, and tests:
337c     -------------------------------
338
339      if(tracer) then
340
341c          when photochem is used, nqchem_min is the rank
342c          of the first chemical species
343
344       if (photochem .or. callthermos) then
345         chem = .true.
346        if (doubleq) then
347          nqchem_min = 3
348        else
349          nqchem_min = dustbin+1
350        end if
351       end if
352
353       if (water .or. thermoswater) h2o = .true.
354
355c          TESTS
356
357       print*,'TRACERS:'
358
359       if ((doubleq).and.(h2o).and.
360     $     (chem).and.(iceparty)) then
361         print*,' 1: dust ; 2: dust (doubleq)'
362         print*,' 3 to ',nqmx-2,': chemistry'
363         print*,nqmx-1,': water ice ; ',nqmx,': water vapor'
364       endif
365
366       if ((doubleq).and.(h2o).and.
367     $     (chem).and..not.(iceparty)) then
368         print*,' 1: dust ; 2: dust (doubleq)'
369         print*,' 3 to ',nqmx-1,': chemistry'
370         print*,nqmx,': water vapor'
371       endif
372
373       if ((doubleq).and.(h2o).and.
374     $     .not.(chem).and.(iceparty)) then
375         print*,' 1: dust ; 2: dust (doubleq)'
376         print*,nqmx-1,': water ice ; ',nqmx,': water vapor'
377         if (nqmx.ne.4) then
378           print*,'nqmx should be 4 with these options...'
379           stop
380         endif
381       endif
382       if ((doubleq).and.(h2o).and.
383     $     .not.(chem).and..not.(iceparty)) then
384         print*,' 1: dust ; 2: dust (doubleq)'
385         print*,nqmx,': water vapor'
386         if (nqmx.ne.3) then
387           print*,'nqmx should be 3 with these options...'
388           stop
389         endif
390       endif
391
392       if ((doubleq).and..not.(h2o)) then
393         print*,' 1: dust ; 2: dust (doubleq)'
394         if (nqmx.ne.2) then
395           print*,'nqmx should be 2 with these options...'
396           stop
397         endif
398       endif
399
400       if (.not.(doubleq).and.(h2o).and.
401     $     (chem).and.(iceparty)) then
402         if (dustbin.gt.0) then
403           print*,' 1 to ',dustbin,': dust bins'
404         endif
405         print*,nqchem_min,' to ',nqmx-2,': chemistry'
406         print*,nqmx-1,': water ice ; ',nqmx,': water vapor'
407       endif
408       if (.not.(doubleq).and.(h2o).and.
409     $     (chem).and..not.(iceparty)) then
410         if (dustbin.gt.0) then
411           print*,' 1 to ',dustbin,': dust bins'
412         endif
413         print*,nqchem_min,' to ',nqmx-1,': chemistry'
414         print*,nqmx,': water vapor'
415       endif
416       if (.not.(doubleq).and.(h2o).and.
417     $     .not.(chem).and.(iceparty)) then
418         if (dustbin.gt.0) then
419           print*,' 1 to ',dustbin,': dust bins'
420         endif
421         print*,nqmx-1,': water ice ; ',nqmx,': water vapor'
422         if (nqmx.ne.(dustbin+2)) then
423           print*,'nqmx should be ',(dustbin+2),
424     $            ' with these options...'
425           stop
426         endif
427       endif
428       if (.not.(doubleq).and.(h2o).and.
429     $     .not.(chem).and..not.(iceparty)) then
430         if (dustbin.gt.0) then
431           print*,' 1 to ',dustbin,': dust bins'
432         endif
433         print*,nqmx,': water vapor'
434         if (nqmx.ne.(dustbin+1)) then
435           print*,'nqmx should be ',(dustbin+1),
436     $            ' with these options...'
437           stop
438         endif
439       endif
440       if (.not.(doubleq).and..not.(h2o)) then
441         if (dustbin.gt.0) then
442           print*,' 1 to ',dustbin,': dust bins'
443           if (nqmx.ne.dustbin) then
444             print*,'nqmx should be ',dustbin,
445     $              ' with these options...'
446             stop
447           endif
448         else
449           print*,'dustbin=',dustbin,
450     $            ': tracer should be F with these options...'
451           stop
452         endif
453       endif
454
455      endif
456
4578000  FORMAT(t5,a12,l8)
4588001  FORMAT(t5,a12,i8)
4598002  FORMAT(t5,a12,f8.1)
460
461      RETURN
462      END
Note: See TracBrowser for help on using the repository browser.