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

Last change on this file since 1047 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 27.1 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! lifting
404         write(*,*)"dust lifted by GCM surface winds ?"
405         lifting=.false. ! default value
406         call getin("lifting",lifting)
407         write(*,*)" lifting = ",lifting
408
409! Test of incompatibility:
410! if lifting is used, then dustbin should be > 0
411
412         if (lifting.and.(dustbin.lt.1)) then
413           print*,'if lifting is used, then dustbin should > 0'
414           stop
415         endif
416! callddevil
417         write(*,*)" dust lifted by dust devils ?"
418         callddevil=.false. !default value
419         call getin("callddevil",callddevil)
420         write(*,*)" callddevil = ",callddevil
421
422! Test of incompatibility:
423! if dustdevil is used, then dustbin should be > 0
424
425         if (callddevil.and.(dustbin.lt.1)) then
426           print*,'if dustdevil is used, then dustbin should > 0'
427           stop
428         endif
429! sedimentation
430         write(*,*) "Gravitationnal sedimentation ?"
431         sedimentation=.true. ! default value
432         call getin("sedimentation",sedimentation)
433         write(*,*) " sedimentation = ",sedimentation
434! activice
435         write(*,*) "Radiatively active transported atmospheric ",
436     &              "water ice ?"
437         activice=.false. ! default value
438         call getin("activice",activice)
439         write(*,*) " activice = ",activice
440! water
441         write(*,*) "Compute water cycle ?"
442         water=.false. ! default value
443         call getin("water",water)
444         write(*,*) " water = ",water
445
446! thermal inertia feedback
447         write(*,*) "Activate the thermal inertia feedback ?"
448         tifeedback=.false. ! default value
449         call getin("tifeedback",tifeedback)
450         write(*,*) " tifeedback = ",tifeedback
451
452! Test of incompatibility:
453
454         if (tifeedback.and..not.water) then
455           print*,'if tifeedback is used,'
456           print*,'water should be used too'
457           stop
458         endif
459
460         if (tifeedback.and..not.callsoil) then
461           print*,'if tifeedback is used,'
462           print*,'callsoil should be used too'
463           stop
464         endif
465
466         if (activice.and..not.water) then
467           print*,'if activice is used, water should be used too'
468           stop
469         endif
470
471         if (water.and..not.tracer) then
472           print*,'if water is used, tracer should be used too'
473           stop
474         endif
475         
476! water ice clouds effective variance distribution for sedimentaion       
477        write(*,*) "effective variance for water ice clouds ?"
478        nuice_sed=0.45
479        call getin("nuice_sed",nuice_sed)
480        write(*,*) "water_param nueff Sedimentation:", nuice_sed
481         
482! ccn factor if no scavenging         
483        write(*,*) "water param CCN reduc. factor ?", ccn_factor
484        ccn_factor = 4.5
485        call getin("ccn_factor",ccn_factor)
486        write(*,*)" ccn_factor = ",ccn_factor
487        write(*,*)"Careful: only used when microphys=F, otherwise"
488        write(*,*)"the contact parameter is used instead;"
489
490! microphys
491         write(*,*)"Microphysical scheme for water-ice clouds?"
492         microphys=.false. ! default value
493         call getin("microphys",microphys)
494         write(*,*)" microphys = ",microphys
495
496! microphysical parameter contact       
497         write(*,*) "water contact parameter ?"
498         mteta  = 0.95
499         call getin("mteta",mteta)
500         write(*,*) "mteta = ", mteta
501
502! scavenging
503         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
504         scavenging=.false. ! default value
505         call getin("scavenging",scavenging)
506         write(*,*)" scavenging = ",scavenging
507         
508
509! Test of incompatibility:
510! if scavenging is used, then dustbin should be > 0
511
512         if ((microphys.and..not.doubleq).or.
513     &       (microphys.and..not.water)) then
514             print*,'if microphys is used, then doubleq,'
515             print*,'and water must be used!'
516             stop
517         endif
518         if (microphys.and..not.scavenging) then
519             print*,''
520             print*,'----------------WARNING-----------------'
521             print*,'microphys is used without scavenging !!!'
522             print*,'----------------WARNING-----------------'
523             print*,''
524         endif
525
526         if ((scavenging.and..not.microphys).or.
527     &       (scavenging.and.(dustbin.lt.1))) then
528             print*,'if scavenging is used, then microphys'
529             print*,'must be used!'
530             stop
531         endif
532
533! Test of incompatibility:
534
535         write(*,*) "Permanent water caps at poles ?",
536     &               " .true. is RECOMMENDED"
537         write(*,*) "(with .true., North cap is a source of water ",
538     &   "and South pole is a cold trap)"
539         caps=.true. ! default value
540         call getin("caps",caps)
541         write(*,*) " caps = ",caps
542
543! albedo_h2o_ice
544         write(*,*) "water ice albedo ?"
545         albedo_h2o_ice=0.45
546         call getin("albedo_h2o_ice",albedo_h2o_ice)
547         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
548! inert_h2o_ice
549         write(*,*) "water ice thermal inertia ?"
550         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
551         call getin("inert_h2o_ice",inert_h2o_ice)
552         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
553! frost_albedo_threshold
554         write(*,*) "frost thickness threshold for albedo ?"
555         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
556         call getin("frost_albedo_threshold",
557     &    frost_albedo_threshold)
558         write(*,*) " frost_albedo_threshold = ",
559     &            frost_albedo_threshold
560
561! call Titus crocus line -- DEFAULT IS NONE
562         write(*,*) "Titus crocus line ?"
563         tituscap=.false.  ! default value
564         call getin("tituscap",tituscap)
565         write(*,*) "tituscap",tituscap
566                     
567
568         write(*,*) "photochemistry: include chemical species"
569         photochem=.false. ! default value
570         call getin("photochem",photochem)
571         write(*,*) " photochem = ",photochem
572
573
574! THERMOSPHERE
575
576         write(*,*) "call thermosphere ?"
577         callthermos=.false. ! default value
578         call getin("callthermos",callthermos)
579         write(*,*) " callthermos = ",callthermos
580         
581
582         write(*,*) " water included without cycle ",
583     &              "(only if water=.false.)"
584         thermoswater=.false. ! default value
585         call getin("thermoswater",thermoswater)
586         write(*,*) " thermoswater = ",thermoswater
587
588         write(*,*) "call thermal conduction ?",
589     &    " (only if callthermos=.true.)"
590         callconduct=.false. ! default value
591         call getin("callconduct",callconduct)
592         write(*,*) " callconduct = ",callconduct
593
594         write(*,*) "call EUV heating ?",
595     &   " (only if callthermos=.true.)"
596         calleuv=.false.  ! default value
597         call getin("calleuv",calleuv)
598         write(*,*) " calleuv = ",calleuv
599
600         write(*,*) "call molecular viscosity ?",
601     &   " (only if callthermos=.true.)"
602         callmolvis=.false. ! default value
603         call getin("callmolvis",callmolvis)
604         write(*,*) " callmolvis = ",callmolvis
605
606         write(*,*) "call molecular diffusion ?",
607     &   " (only if callthermos=.true.)"
608         callmoldiff=.false. ! default value
609         call getin("callmoldiff",callmoldiff)
610         write(*,*) " callmoldiff = ",callmoldiff
611         
612
613         write(*,*) "call thermospheric photochemistry ?",
614     &   " (only if callthermos=.true.)"
615         thermochem=.false. ! default value
616         call getin("thermochem",thermochem)
617         write(*,*) " thermochem = ",thermochem
618
619         write(*,*) "Method to include solar variability"
620         write(*,*) "0-> old method (using solarcondate); ",
621     &                  "1-> variability wit E10.7"
622         solvarmod=1
623         call getin("solvarmod",solvarmod)
624         write(*,*) " solvarmod = ",solvarmod
625
626         write(*,*) "date for solar flux calculation:",
627     &   " (1985 < date < 2002)",
628     $   " (Only used if solvarmod=0)"
629         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
630         solarcondate=1993.4 ! default value
631         call getin("solarcondate",solarcondate)
632         write(*,*) " solarcondate = ",solarcondate
633         
634         write(*,*) "Solar variability as observed for MY: "
635         write(*,*) "Only if solvarmod=1"
636         solvaryear=24
637         call getin("solvaryear",solvaryear)
638         write(*,*) " solvaryear = ",solvaryear
639
640         write(*,*) "UV heating efficiency:",
641     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
642     &   "lower values may be used to compensate low 15 um cooling"
643         euveff=0.21 !default value
644         call getin("euveff",euveff)
645         write(*,*) " euveff = ", euveff
646
647         if (.not.callthermos) then
648           if (thermoswater) then
649             print*,'if thermoswater is set, callthermos must be true'
650             stop
651           endif         
652           if (callconduct) then
653             print*,'if callconduct is set, callthermos must be true'
654             stop
655           endif       
656           if (calleuv) then
657             print*,'if calleuv is set, callthermos must be true'
658             stop
659           endif         
660           if (callmolvis) then
661             print*,'if callmolvis is set, callthermos must be true'
662             stop
663           endif       
664           if (callmoldiff) then
665             print*,'if callmoldiff is set, callthermos must be true'
666             stop
667           endif         
668           if (thermochem) then
669             print*,'if thermochem is set, callthermos must be true'
670             stop
671           endif         
672        endif
673
674! Test of incompatibility:
675! if photochem is used, then water should be used too
676
677         if (photochem.and..not.water) then
678           print*,'if photochem is used, water should be used too'
679           stop
680         endif
681
682! if callthermos is used, then thermoswater should be used too
683! (if water not used already)
684
685         if (callthermos .and. .not.water) then
686           if (callthermos .and. .not.thermoswater) then
687             print*,'if callthermos is used, water or thermoswater
688     &               should be used too'
689             stop
690           endif
691         endif
692
693         PRINT*,'--------------------------------------------'
694         PRINT*
695         PRINT*
696      ELSE
697         write(*,*)
698         write(*,*) 'Cannot read file callphys.def. Is it here ?'
699         stop
700      ENDIF
701
7028000  FORMAT(t5,a12,l8)
7038001  FORMAT(t5,a12,i8)
704
705      PRINT*
706      PRINT*,'inifis: daysec',daysec
707      PRINT*
708      PRINT*,'inifis: The radiative transfer is computed:'
709      PRINT*,'           each ',iradia,' physical time-step'
710      PRINT*,'        or each ',iradia*dtphys,' seconds'
711      PRINT*
712! --------------------------------------------------------------
713!  Managing the Longwave radiative transfer
714! --------------------------------------------------------------
715
716!     In most cases, the run just use the following values :
717!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
718      callemis=.true.     
719!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
720      ilwd=1
721      ilwn=1 !2
722      ilwb=1 !2
723      linear=.true.       
724      ncouche=3
725      alphan=0.4
726      semi=0
727
728!     BUT people working hard on the LW may want to read them in 'radia.def'
729!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
730
731      OPEN(99,file='radia.def',status='old',form='formatted'
732     .     ,iostat=ierr)
733      IF(ierr.EQ.0) THEN
734         write(*,*) 'inifis: Reading radia.def !!!'
735         READ(99,fmt='(a)') ch1
736         READ(99,*) callemis
737         WRITE(*,8000) ch1,callemis
738
739         READ(99,fmt='(a)') ch1
740         READ(99,*) iradia
741         WRITE(*,8001) ch1,iradia
742
743         READ(99,fmt='(a)') ch1
744         READ(99,*) ilwd
745         WRITE(*,8001) ch1,ilwd
746
747         READ(99,fmt='(a)') ch1
748         READ(99,*) ilwn
749         WRITE(*,8001) ch1,ilwn
750
751         READ(99,fmt='(a)') ch1
752         READ(99,*) linear
753         WRITE(*,8000) ch1,linear
754
755         READ(99,fmt='(a)') ch1
756         READ(99,*) ncouche
757         WRITE(*,8001) ch1,ncouche
758
759         READ(99,fmt='(a)') ch1
760         READ(99,*) alphan
761         WRITE(*,*) ch1,alphan
762
763         READ(99,fmt='(a)') ch1
764         READ(99,*) ilwb
765         WRITE(*,8001) ch1,ilwb
766
767
768         READ(99,fmt='(a)') ch1
769         READ(99,'(l1)') callg2d
770         WRITE(*,8000) ch1,callg2d
771
772         READ(99,fmt='(a)') ch1
773         READ(99,*) semi
774         WRITE(*,*) ch1,semi
775      end if
776      CLOSE(99)
777
778!-----------------------------------------------------------------------
779!     Some more initialization:
780!     ------------------------
781
782      ! allocate "slope_mod" arrays
783      call ini_slope_mod(ngrid)
784     
785      ! allocate "comsaison_h" arrays
786      call ini_comsaison_h(ngrid)
787     
788      ! allocate "surfdat_h" arrays
789      call ini_surfdat_h(ngrid)
790     
791      ! allocate "comgeomfi_h" arrays
792      allocate(lati(ngrid))
793      allocate(long(ngrid))
794      allocate(area(ngrid))
795     
796      ! fill "comgeomfi_h" data
797      CALL SCOPY(ngrid,plon,1,long,1)
798      CALL SCOPY(ngrid,plat,1,lati,1)
799      CALL SCOPY(ngrid,parea,1,area,1)
800      totarea=SSUM(ngrid,area,1)
801
802      ! allocate "comdiurn_h" data
803      allocate(sinlat(ngrid))
804      allocate(coslat(ngrid))
805      allocate(sinlon(ngrid))
806      allocate(coslon(ngrid))
807     
808      ! fill "comdiurn_h" data
809      DO ig=1,ngrid
810         sinlat(ig)=sin(plat(ig))
811         coslat(ig)=cos(plat(ig))
812         sinlon(ig)=sin(plon(ig))
813         coslon(ig)=cos(plon(ig))
814      ENDDO
815
816      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
817
818      ! allocate "comsoil_h" arrays
819      call ini_comsoil_h(ngrid)
820           
821      ! set some variables in "dimradmars_mod"
822      call ini_dimradmars_mod(ngrid,nlayer)
823     
824      ! allocate arrays in "yomaer_h"
825      call ini_yomaer_h
826     
827      ! allocate arrays in "yomlw_h"
828      call ini_yomlw_h(ngrid)
829     
830      ! allocate arrays in "conc_mod"
831      call ini_conc_mod(ngrid,nlayer)
832     
833      END
Note: See TracBrowser for help on using the repository browser.