source: trunk/LMDZ.MARS/libf/phymars/inifis.F @ 1106

Last change on this file since 1106 was 1106, checked in by tnavarro, 11 years ago

option freedust with ice microphysics & masse naming in start files

File size: 27.7 KB
Line 
1      SUBROUTINE inifis(
2     $           ngrid,nlayer,nq
3     $           ,day_ini,pdaysec,ptimestep
4     $           ,plat,plon,parea
5     $           ,prad,pg,pr,pcpp
6#ifdef MESOSCALE
7#include "meso_inc/meso_inc_inifisinvar.F"
8#endif
9     $           )
10!
11!=======================================================================
12!
13!   purpose:
14!   -------
15!
16!   Initialisation for the physical parametrisations of the LMD
17!   martian atmospheric general circulation modele.
18!
19!   author: Frederic Hourdin 15 / 10 /93
20!   -------
21!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
22!             Ehouarn Millour (oct. 2008) tracers are now identified
23!              by their names and may not be contiguously
24!              stored in the q(:,:,:,:) array
25!             E.M. (june 2009) use getin routine to load parameters
26!             adapted to the mesoscale use - Aymeric Spiga - 01/2007-07/2011
27!
28!
29!   arguments:
30!   ----------
31!
32!   input:
33!   ------
34!
35!    ngrid                 Size of the horizontal grid.
36!                          All internal loops are performed on that grid.
37!    nlayer                Number of vertical layers.
38!    pdayref               Day of reference for the simulation
39!    pday                  Number of days counted from the North. Spring
40!                          equinoxe.
41!
42!=======================================================================
43!
44!-----------------------------------------------------------------------
45!   declarations:
46!   -------------
47! to use  'getin'
48      USE ioipsl_getincom, only : getin
49      use tracer_mod, only : nqmx, nuice_sed, ccn_factor
50      use comsoil_h, only: ini_comsoil_h
51#ifdef MESOSCALE
52      use comsoil_h, only: volcapa !!MESOSCALE -- needed to fill volcapa
53#endif     
54      use comgeomfi_h, only: long, lati, area, totarea
55      use comdiurn_h, only: sinlat, coslat, sinlon, coslon
56      use surfdat_h, only: ini_surfdat_h, albedo_h2o_ice, inert_h2o_ice,
57     &                     frost_albedo_threshold
58      use comsaison_h, only: ini_comsaison_h
59      use slope_mod, only: ini_slope_mod
60      use dimradmars_mod, only: ini_dimradmars_mod
61      use yomaer_h,only: ini_yomaer_h, tauvis
62      use yomlw_h, only: ini_yomlw_h
63      use conc_mod, only: ini_conc_mod
64      IMPLICIT NONE
65#include "dimensions.h"
66#include "dimphys.h"
67#include "planete.h"
68#include "comcstfi.h"
69!#include "comsaison.h"
70!#include "comdiurn.h"
71!#include "comgeomfi.h"
72#include "callkeys.h"
73!#include "surfdat.h"
74!#include "dimradmars.h"
75!#include "yomaer.h"
76#include "datafile.h"
77!#include "slope.h"
78#include "microphys.h"
79!#include "tracer.h"
80! naerkind is set in scatterers.h (built when compiling with makegcm -s #)
81#include"scatterers.h"
82#ifdef MESOSCALE
83!#include "comsoil.h"     !!MESOSCALE -- needed to fill volcapa
84#include "meso_inc/meso_inc_inifisvar.F"
85#endif
86      REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec
87
88      REAL,INTENT(IN) :: ptimestep
89      INTEGER,INTENT(IN) :: day_ini
90
91      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
92      REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
93      INTEGER ig,ierr
94 
95!      EXTERNAL iniorbit,orbite
96      EXTERNAL SSUM
97      REAL SSUM
98 
99      CHARACTER ch1*12
100      CHARACTER ch80*80
101
102!      logical chem, h2o
103
104!      chem = .false.
105!      h2o = .false.
106
107      rad=prad
108      cpp=pcpp
109      g=pg
110      r=pr
111      rcp=r/cpp
112      daysec=pdaysec
113      dtphys=ptimestep
114
115      nqmx=nq
116
117#ifdef MESOSCALE
118#include "meso_inc/meso_inc_inifisini.F"
119#endif
120
121! --------------------------------------------------------
122!     The usual Tests
123!     --------------
124!      IF (nlayer.NE.nlayermx) THEN
125!         PRINT*,'STOP in inifis'
126!         PRINT*,'Probleme de dimensions :'
127!         PRINT*,'nlayer     = ',nlayer
128!         PRINT*,'nlayermx   = ',nlayermx
129!         STOP
130!      ENDIF
131
132!      IF (ngrid.NE.ngridmx) THEN
133!         PRINT*,'STOP in inifis'
134!         PRINT*,'Probleme de dimensions :'
135!         PRINT*,'ngrid     = ',ngrid
136!         PRINT*,'ngridmx   = ',ngridmx
137!         STOP
138!      ENDIF
139
140! --------------------------------------------------------------
141!  Reading the "callphys.def" file controlling some key options
142! --------------------------------------------------------------
143     
144      ! check that 'callphys.def' file is around
145      OPEN(99,file='callphys.def',status='old',form='formatted'
146     &     ,iostat=ierr)
147      CLOSE(99)
148     
149      IF(ierr.EQ.0) THEN
150         PRINT*
151         PRINT*
152         PRINT*,'--------------------------------------------'
153         PRINT*,' inifis: Parameters for the physics (callphys.def)'
154         PRINT*,'--------------------------------------------'
155
156         write(*,*) "Directory where external input files are:"
157         datafile="/u/forget/WWW/datagcm/datafile"
158         call getin("datadir",datafile) ! default path
159         write(*,*) " datafile = ",trim(datafile)
160
161         write(*,*) "Run with or without tracer transport ?"
162         tracer=.false. ! default value
163         call getin("tracer",tracer)
164         write(*,*) " tracer = ",tracer
165
166         write(*,*) "Diurnal cycle ?"
167         write(*,*) "(if diurnal=False, diurnal averaged solar heating)"
168         diurnal=.true. ! default value
169         call getin("diurnal",diurnal)
170         write(*,*) " diurnal = ",diurnal
171
172         write(*,*) "Seasonal cycle ?"
173         write(*,*) "(if season=False, Ls stays constant, to value ",
174     &   "set in 'start'"
175         season=.true. ! default value
176         call getin("season",season)
177         write(*,*) " season = ",season
178
179         write(*,*) "Write some extra output to the screen ?"
180         lwrite=.false. ! default value
181         call getin("lwrite",lwrite)
182         write(*,*) " lwrite = ",lwrite
183
184         write(*,*) "Save statistics in file stats.nc ?"
185#ifdef MESOSCALE
186         callstats=.false. ! default value
187#else
188         callstats=.true. ! default value
189#endif
190         call getin("callstats",callstats)
191         write(*,*) " callstats = ",callstats
192
193         write(*,*) "Save EOF profiles in file 'profiles' for ",
194     &              "Climate Database?"
195         calleofdump=.false. ! default value
196         call getin("calleofdump",calleofdump)
197         write(*,*) " calleofdump = ",calleofdump
198
199         write(*,*) "Dust scenario: 1=constant dust (read from startfi",
200     &   " or set as tauvis); 2=Viking scenario; =3 MGS scenario,",
201     &   "=6 cold (low dust) scenario; =7 warm (high dust) scenario ",
202     &   "=24,25 ... 30 :Mars Year 24, ... or 30 from TES assimilation"
203         iaervar=3 ! default value
204         call getin("iaervar",iaervar)
205         write(*,*) " iaervar = ",iaervar
206
207         write(*,*) "Reference (visible) dust opacity at 610 Pa ",
208     &   "(matters only if iaervar=1)"
209         ! NB: default value of tauvis is set/read in startfi.nc file
210         call getin("tauvis",tauvis)
211         write(*,*) " tauvis = ",tauvis
212
213         write(*,*) "Dust vertical distribution:"
214         write(*,*) "(=1 top set by topdustref parameter;",
215     & " =2 Viking scenario; =3 MGS scenario)"
216         iddist=3 ! default value
217         call getin("iddist",iddist)
218         write(*,*) " iddist = ",iddist
219
220         write(*,*) "Dust top altitude (km). (Matters only if iddist=1)"
221         topdustref= 90.0 ! default value
222         call getin("topdustref",topdustref)
223         write(*,*) " topdustref = ",topdustref
224
225         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
226         tke_heat_flux=0. ! default value
227         call getin("tke_heat_flux",tke_heat_flux)
228         write(*,*) " tke_heat_flux = ",tke_heat_flux
229         write(*,*) " 0 means the usual schemes are computing"
230
231         write(*,*) "call radiative transfer ?"
232         callrad=.true. ! default value
233         call getin("callrad",callrad)
234         write(*,*) " callrad = ",callrad
235
236         write(*,*) "call slope insolation scheme ?",
237     &              "(matters only if callrad=T)"
238#ifdef MESOSCALE
239         callslope=.true. ! default value
240#else
241         callslope=.false. ! default value (not supported yet)
242#endif
243         call getin("callslope",callslope)
244         write(*,*) " callslope = ",callslope
245
246         write(*,*) "call NLTE radiative schemes ?",
247     &              "(matters only if callrad=T)"
248         callnlte=.false. ! default value
249         call getin("callnlte",callnlte)
250         write(*,*) " callnlte = ",callnlte
251         
252         nltemodel=0    !default value
253         write(*,*) "NLTE model?"
254         write(*,*) "0 -> old model, static O"
255         write(*,*) "1 -> old model, dynamic O"
256         write(*,*) "2 -> new model"
257         write(*,*) "(matters only if callnlte=T)"
258         call getin("nltemodel",nltemodel)
259         write(*,*) " nltemodel = ",nltemodel
260
261         write(*,*) "call CO2 NIR absorption ?",
262     &              "(matters only if callrad=T)"
263         callnirco2=.false. ! default value
264         call getin("callnirco2",callnirco2)
265         write(*,*) " callnirco2 = ",callnirco2
266
267         write(*,*) "New NIR NLTE correction ?",
268     $              "0-> old model (no correction)",
269     $              "1-> new correction",
270     $              "(matters only if callnirco2=T)"
271#ifdef MESOSCALE
272         nircorr=0      !default value. this is OK below 60 km.
273#else
274         nircorr=0      !default value
275#endif
276         call getin("nircorr",nircorr)
277         write(*,*) " nircorr = ",nircorr
278
279         write(*,*) "call turbulent vertical diffusion ?"
280         calldifv=.true. ! default value
281         call getin("calldifv",calldifv)
282         write(*,*) " calldifv = ",calldifv
283
284         write(*,*) "call thermals ?"
285         calltherm=.false. ! default value
286         call getin("calltherm",calltherm)
287         write(*,*) " calltherm = ",calltherm
288
289         write(*,*) "call convective adjustment ?"
290         calladj=.true. ! default value
291         call getin("calladj",calladj)
292         write(*,*) " calladj = ",calladj
293         
294         if (calltherm .and. (.not. calladj)) then
295          print*,'Convadj has to be activated when using thermals'
296          stop
297         endif
298
299         write(*,*) "call Richardson-based surface layer ?"
300         callrichsl=.false. ! default value
301         call getin("callrichsl",callrichsl)
302         write(*,*) " callrichsl = ",callrichsl
303
304         if (calltherm .and. .not.callrichsl) then
305          print*,'WARNING WARNING WARNING'
306          print*,'if calltherm=T we strongly advise that '
307          print*,'you use the new surface layer scheme '
308          print*,'by setting callrichsl=T '
309         endif
310
311         if (calladj .and. callrichsl .and. (.not. calltherm)) then
312          print*,'You should not be calling the convective adjustment
313     & scheme with the Richardson surface-layer and without the thermals
314     &. This approach is not
315     & physically consistent and can lead to unrealistic friction
316     & values.'
317          print*,'If you want to use the Ri. surface-layer, either
318     & activate thermals OR de-activate the convective adjustment.'
319          stop
320         endif
321
322         write(*,*) "call CO2 condensation ?"
323         callcond=.true. ! default value
324         call getin("callcond",callcond)
325         write(*,*) " callcond = ",callcond
326
327         write(*,*)"call thermal conduction in the soil ?"
328         callsoil=.true. ! default value
329         call getin("callsoil",callsoil)
330         write(*,*) " callsoil = ",callsoil
331         
332
333         write(*,*)"call Lott's gravity wave/subgrid topography ",
334     &             "scheme ?"
335         calllott=.true. ! default value
336         call getin("calllott",calllott)
337         write(*,*)" calllott = ",calllott
338
339
340         write(*,*)"rad.transfer is computed every iradia",
341     &             " physical timestep"
342         iradia=1 ! default value
343         call getin("iradia",iradia)
344         write(*,*)" iradia = ",iradia
345         
346
347         write(*,*)"Output of the exchange coefficient mattrix ?",
348     &             "(for diagnostics only)"
349         callg2d=.false. ! default value
350         call getin("callg2d",callg2d)
351         write(*,*)" callg2d = ",callg2d
352
353         write(*,*)"Rayleigh scattering : (should be .false. for now)"
354         rayleigh=.false.
355         call getin("rayleigh",rayleigh)
356         write(*,*)" rayleigh = ",rayleigh
357
358
359! TRACERS:
360
361! dustbin
362         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
363         dustbin=0 ! default value
364         call getin("dustbin",dustbin)
365         write(*,*)" dustbin = ",dustbin
366! active
367         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
368         active=.false. ! default value
369         call getin("active",active)
370         write(*,*)" active = ",active
371
372! Test of incompatibility:
373! if active is used, then dustbin should be > 0
374
375         if (active.and.(dustbin.lt.1)) then
376           print*,'if active is used, then dustbin should > 0'
377           stop
378         endif
379! doubleq
380         write(*,*)"use mass and number mixing ratios to predict",
381     &             " dust size ?"
382         doubleq=.false. ! default value
383         call getin("doubleq",doubleq)
384         write(*,*)" doubleq = ",doubleq
385! submicron
386         submicron=.false. ! default value
387         call getin("submicron",submicron)
388         write(*,*)" submicron = ",submicron
389
390! Test of incompatibility:
391! if doubleq is used, then dustbin should be 2
392
393         if (doubleq.and.(dustbin.ne.2)) then
394           print*,'if doubleq is used, then dustbin should be 2'
395           stop
396         endif
397         if (doubleq.and.submicron.and.(nq.LT.3)) then
398           print*,'If doubleq is used with a submicron tracer,'
399           print*,' then the number of tracers has to be'
400           print*,' larger than 3.'
401           stop
402         endif
403
404! lifting
405         write(*,*)"dust lifted by GCM surface winds ?"
406         lifting=.false. ! default value
407         call getin("lifting",lifting)
408         write(*,*)" lifting = ",lifting
409
410! Test of incompatibility:
411! if lifting is used, then dustbin should be > 0
412
413         if (lifting.and.(dustbin.lt.1)) then
414           print*,'if lifting is used, then dustbin should > 0'
415           stop
416         endif
417
418! free evolving dust
419! freedust=true just says that there is no lifting and no dust opacity scaling.
420         write(*,*)"dust lifted by GCM surface winds ?"
421         freedust=.false. ! default value
422         call getin("freedust",freedust)
423         write(*,*)" freedust = ",freedust
424         if (freedust.and..not.doubleq) then
425           print*,'freedust should be used with doubleq !'
426           stop
427         endif
428         if (freedust.and.lifting) then
429           print*,'if freedust is used, then lifting should not be used'
430           print*,'lifting forced to false !!'
431           lifting=.false.
432         endif
433
434! callddevil
435         write(*,*)" dust lifted by dust devils ?"
436         callddevil=.false. !default value
437         call getin("callddevil",callddevil)
438         write(*,*)" callddevil = ",callddevil
439
440! Test of incompatibility:
441! if dustdevil is used, then dustbin should be > 0
442
443         if (callddevil.and.(dustbin.lt.1)) then
444           print*,'if dustdevil is used, then dustbin should > 0'
445           stop
446         endif
447! sedimentation
448         write(*,*) "Gravitationnal sedimentation ?"
449         sedimentation=.true. ! default value
450         call getin("sedimentation",sedimentation)
451         write(*,*) " sedimentation = ",sedimentation
452! activice
453         write(*,*) "Radiatively active transported atmospheric ",
454     &              "water ice ?"
455         activice=.false. ! default value
456         call getin("activice",activice)
457         write(*,*) " activice = ",activice
458! water
459         write(*,*) "Compute water cycle ?"
460         water=.false. ! default value
461         call getin("water",water)
462         write(*,*) " water = ",water
463
464! thermal inertia feedback
465         write(*,*) "Activate the thermal inertia feedback ?"
466         tifeedback=.false. ! default value
467         call getin("tifeedback",tifeedback)
468         write(*,*) " tifeedback = ",tifeedback
469
470! Test of incompatibility:
471
472         if (tifeedback.and..not.water) then
473           print*,'if tifeedback is used,'
474           print*,'water should be used too'
475           stop
476         endif
477
478         if (tifeedback.and..not.callsoil) then
479           print*,'if tifeedback is used,'
480           print*,'callsoil should be used too'
481           stop
482         endif
483
484         if (activice.and..not.water) then
485           print*,'if activice is used, water should be used too'
486           stop
487         endif
488
489         if (water.and..not.tracer) then
490           print*,'if water is used, tracer should be used too'
491           stop
492         endif
493         
494! water ice clouds effective variance distribution for sedimentaion       
495        write(*,*) "effective variance for water ice clouds ?"
496        nuice_sed=0.45
497        call getin("nuice_sed",nuice_sed)
498        write(*,*) "water_param nueff Sedimentation:", nuice_sed
499         
500! ccn factor if no scavenging         
501        write(*,*) "water param CCN reduc. factor ?", ccn_factor
502        ccn_factor = 4.5
503        call getin("ccn_factor",ccn_factor)
504        write(*,*)" ccn_factor = ",ccn_factor
505        write(*,*)"Careful: only used when microphys=F, otherwise"
506        write(*,*)"the contact parameter is used instead;"
507
508! microphys
509         write(*,*)"Microphysical scheme for water-ice clouds?"
510         microphys=.false. ! default value
511         call getin("microphys",microphys)
512         write(*,*)" microphys = ",microphys
513
514! microphysical parameter contact       
515         write(*,*) "water contact parameter ?"
516         mteta  = 0.95
517         call getin("mteta",mteta)
518         write(*,*) "mteta = ", mteta
519
520! scavenging
521         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
522         scavenging=.false. ! default value
523         call getin("scavenging",scavenging)
524         write(*,*)" scavenging = ",scavenging
525         
526
527! Test of incompatibility:
528! if scavenging is used, then dustbin should be > 0
529
530         if ((microphys.and..not.doubleq).or.
531     &       (microphys.and..not.water)) then
532             print*,'if microphys is used, then doubleq,'
533             print*,'and water must be used!'
534             stop
535         endif
536         if (microphys.and..not.scavenging) then
537             print*,''
538             print*,'----------------WARNING-----------------'
539             print*,'microphys is used without scavenging !!!'
540             print*,'----------------WARNING-----------------'
541             print*,''
542         endif
543
544         if ((scavenging.and..not.microphys).or.
545     &       (scavenging.and.(dustbin.lt.1))) then
546             print*,'if scavenging is used, then microphys'
547             print*,'must be used!'
548             stop
549         endif
550
551! Test of incompatibility:
552
553         write(*,*) "Permanent water caps at poles ?",
554     &               " .true. is RECOMMENDED"
555         write(*,*) "(with .true., North cap is a source of water ",
556     &   "and South pole is a cold trap)"
557         caps=.true. ! default value
558         call getin("caps",caps)
559         write(*,*) " caps = ",caps
560
561! albedo_h2o_ice
562         write(*,*) "water ice albedo ?"
563         albedo_h2o_ice=0.45
564         call getin("albedo_h2o_ice",albedo_h2o_ice)
565         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
566! inert_h2o_ice
567         write(*,*) "water ice thermal inertia ?"
568         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
569         call getin("inert_h2o_ice",inert_h2o_ice)
570         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
571! frost_albedo_threshold
572         write(*,*) "frost thickness threshold for albedo ?"
573         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
574         call getin("frost_albedo_threshold",
575     &    frost_albedo_threshold)
576         write(*,*) " frost_albedo_threshold = ",
577     &            frost_albedo_threshold
578
579! call Titus crocus line -- DEFAULT IS NONE
580         write(*,*) "Titus crocus line ?"
581         tituscap=.false.  ! default value
582         call getin("tituscap",tituscap)
583         write(*,*) "tituscap",tituscap
584                     
585
586         write(*,*) "photochemistry: include chemical species"
587         photochem=.false. ! default value
588         call getin("photochem",photochem)
589         write(*,*) " photochem = ",photochem
590
591
592! THERMOSPHERE
593
594         write(*,*) "call thermosphere ?"
595         callthermos=.false. ! default value
596         call getin("callthermos",callthermos)
597         write(*,*) " callthermos = ",callthermos
598         
599
600         write(*,*) " water included without cycle ",
601     &              "(only if water=.false.)"
602         thermoswater=.false. ! default value
603         call getin("thermoswater",thermoswater)
604         write(*,*) " thermoswater = ",thermoswater
605
606         write(*,*) "call thermal conduction ?",
607     &    " (only if callthermos=.true.)"
608         callconduct=.false. ! default value
609         call getin("callconduct",callconduct)
610         write(*,*) " callconduct = ",callconduct
611
612         write(*,*) "call EUV heating ?",
613     &   " (only if callthermos=.true.)"
614         calleuv=.false.  ! default value
615         call getin("calleuv",calleuv)
616         write(*,*) " calleuv = ",calleuv
617
618         write(*,*) "call molecular viscosity ?",
619     &   " (only if callthermos=.true.)"
620         callmolvis=.false. ! default value
621         call getin("callmolvis",callmolvis)
622         write(*,*) " callmolvis = ",callmolvis
623
624         write(*,*) "call molecular diffusion ?",
625     &   " (only if callthermos=.true.)"
626         callmoldiff=.false. ! default value
627         call getin("callmoldiff",callmoldiff)
628         write(*,*) " callmoldiff = ",callmoldiff
629         
630
631         write(*,*) "call thermospheric photochemistry ?",
632     &   " (only if callthermos=.true.)"
633         thermochem=.false. ! default value
634         call getin("thermochem",thermochem)
635         write(*,*) " thermochem = ",thermochem
636
637         write(*,*) "Method to include solar variability"
638         write(*,*) "0-> old method (using solarcondate); ",
639     &                  "1-> variability wit E10.7"
640         solvarmod=1
641         call getin("solvarmod",solvarmod)
642         write(*,*) " solvarmod = ",solvarmod
643
644         write(*,*) "date for solar flux calculation:",
645     &   " (1985 < date < 2002)",
646     $   " (Only used if solvarmod=0)"
647         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
648         solarcondate=1993.4 ! default value
649         call getin("solarcondate",solarcondate)
650         write(*,*) " solarcondate = ",solarcondate
651         
652         write(*,*) "Solar variability as observed for MY: "
653         write(*,*) "Only if solvarmod=1"
654         solvaryear=24
655         call getin("solvaryear",solvaryear)
656         write(*,*) " solvaryear = ",solvaryear
657
658         write(*,*) "UV heating efficiency:",
659     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
660     &   "lower values may be used to compensate low 15 um cooling"
661         euveff=0.21 !default value
662         call getin("euveff",euveff)
663         write(*,*) " euveff = ", euveff
664
665         if (.not.callthermos) then
666           if (thermoswater) then
667             print*,'if thermoswater is set, callthermos must be true'
668             stop
669           endif         
670           if (callconduct) then
671             print*,'if callconduct is set, callthermos must be true'
672             stop
673           endif       
674           if (calleuv) then
675             print*,'if calleuv is set, callthermos must be true'
676             stop
677           endif         
678           if (callmolvis) then
679             print*,'if callmolvis is set, callthermos must be true'
680             stop
681           endif       
682           if (callmoldiff) then
683             print*,'if callmoldiff is set, callthermos must be true'
684             stop
685           endif         
686           if (thermochem) then
687             print*,'if thermochem is set, callthermos must be true'
688             stop
689           endif         
690        endif
691
692! Test of incompatibility:
693! if photochem is used, then water should be used too
694
695         if (photochem.and..not.water) then
696           print*,'if photochem is used, water should be used too'
697           stop
698         endif
699
700! if callthermos is used, then thermoswater should be used too
701! (if water not used already)
702
703         if (callthermos .and. .not.water) then
704           if (callthermos .and. .not.thermoswater) then
705             print*,'if callthermos is used, water or thermoswater
706     &               should be used too'
707             stop
708           endif
709         endif
710
711         PRINT*,'--------------------------------------------'
712         PRINT*
713         PRINT*
714      ELSE
715         write(*,*)
716         write(*,*) 'Cannot read file callphys.def. Is it here ?'
717         stop
718      ENDIF
719
7208000  FORMAT(t5,a12,l8)
7218001  FORMAT(t5,a12,i8)
722
723      PRINT*
724      PRINT*,'inifis: daysec',daysec
725      PRINT*
726      PRINT*,'inifis: The radiative transfer is computed:'
727      PRINT*,'           each ',iradia,' physical time-step'
728      PRINT*,'        or each ',iradia*dtphys,' seconds'
729      PRINT*
730! --------------------------------------------------------------
731!  Managing the Longwave radiative transfer
732! --------------------------------------------------------------
733
734!     In most cases, the run just use the following values :
735!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
736      callemis=.true.     
737!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
738      ilwd=1
739      ilwn=1 !2
740      ilwb=1 !2
741      linear=.true.       
742      ncouche=3
743      alphan=0.4
744      semi=0
745
746!     BUT people working hard on the LW may want to read them in 'radia.def'
747!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
748
749      OPEN(99,file='radia.def',status='old',form='formatted'
750     .     ,iostat=ierr)
751      IF(ierr.EQ.0) THEN
752         write(*,*) 'inifis: Reading radia.def !!!'
753         READ(99,fmt='(a)') ch1
754         READ(99,*) callemis
755         WRITE(*,8000) ch1,callemis
756
757         READ(99,fmt='(a)') ch1
758         READ(99,*) iradia
759         WRITE(*,8001) ch1,iradia
760
761         READ(99,fmt='(a)') ch1
762         READ(99,*) ilwd
763         WRITE(*,8001) ch1,ilwd
764
765         READ(99,fmt='(a)') ch1
766         READ(99,*) ilwn
767         WRITE(*,8001) ch1,ilwn
768
769         READ(99,fmt='(a)') ch1
770         READ(99,*) linear
771         WRITE(*,8000) ch1,linear
772
773         READ(99,fmt='(a)') ch1
774         READ(99,*) ncouche
775         WRITE(*,8001) ch1,ncouche
776
777         READ(99,fmt='(a)') ch1
778         READ(99,*) alphan
779         WRITE(*,*) ch1,alphan
780
781         READ(99,fmt='(a)') ch1
782         READ(99,*) ilwb
783         WRITE(*,8001) ch1,ilwb
784
785
786         READ(99,fmt='(a)') ch1
787         READ(99,'(l1)') callg2d
788         WRITE(*,8000) ch1,callg2d
789
790         READ(99,fmt='(a)') ch1
791         READ(99,*) semi
792         WRITE(*,*) ch1,semi
793      end if
794      CLOSE(99)
795
796!-----------------------------------------------------------------------
797!     Some more initialization:
798!     ------------------------
799
800      ! allocate "slope_mod" arrays
801      call ini_slope_mod(ngrid)
802     
803      ! allocate "comsaison_h" arrays
804      call ini_comsaison_h(ngrid)
805     
806      ! allocate "surfdat_h" arrays
807      call ini_surfdat_h(ngrid)
808     
809      ! allocate "comgeomfi_h" arrays
810      allocate(lati(ngrid))
811      allocate(long(ngrid))
812      allocate(area(ngrid))
813     
814      ! fill "comgeomfi_h" data
815      CALL SCOPY(ngrid,plon,1,long,1)
816      CALL SCOPY(ngrid,plat,1,lati,1)
817      CALL SCOPY(ngrid,parea,1,area,1)
818      totarea=SSUM(ngrid,area,1)
819
820      ! allocate "comdiurn_h" data
821      allocate(sinlat(ngrid))
822      allocate(coslat(ngrid))
823      allocate(sinlon(ngrid))
824      allocate(coslon(ngrid))
825     
826      ! fill "comdiurn_h" data
827      DO ig=1,ngrid
828         sinlat(ig)=sin(plat(ig))
829         coslat(ig)=cos(plat(ig))
830         sinlon(ig)=sin(plon(ig))
831         coslon(ig)=cos(plon(ig))
832      ENDDO
833
834      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
835
836      ! allocate "comsoil_h" arrays
837      call ini_comsoil_h(ngrid)
838           
839      ! set some variables in "dimradmars_mod"
840      call ini_dimradmars_mod(ngrid,nlayer)
841     
842      ! allocate arrays in "yomaer_h"
843      call ini_yomaer_h
844     
845      ! allocate arrays in "yomlw_h"
846      call ini_yomlw_h(ngrid)
847     
848      ! allocate arrays in "conc_mod"
849      call ini_conc_mod(ngrid,nlayer)
850     
851      END
Note: See TracBrowser for help on using the repository browser.