source: trunk/LMDZ.GENERIC/libf/phystd/inifis.F @ 1255

Last change on this file since 1255 was 1252, checked in by aslmd, 11 years ago

LMDZ.GENERIC LMDZ.COMMON LMDZ.UNIVERSAL. Bye Bye LMDZ.UNIVERSAL. Go to LMDZ.COMMON!

File size: 23.2 KB
Line 
1      SUBROUTINE inifis(ngrid,nlayer,nq,
2     $           day_ini,pdaysec,ptimestep,
3     $           plat,plon,parea,
4     $           prad,pg,pr,pcpp)
5
6      use radinc_h, only : naerkind
7      use datafile_mod, only: datadir
8      use comdiurn_h, only: sinlat, coslat, sinlon, coslon
9      use comgeomfi_h, only: long, lati, area, totarea
10      use comsoil_h, only: ini_comsoil_h
11      use control_mod, only: ecritphy
12
13!=======================================================================
14!
15!   purpose:
16!   -------
17!
18!   Initialisation for the physical parametrisations of the LMD
19!   Generic Model.
20!
21!   author: Frederic Hourdin 15 / 10 /93
22!   -------
23!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
24!             Ehouarn Millour (oct. 2008) tracers are now identified
25!              by their names and may not be contiguously
26!              stored in the q(:,:,:,:) array
27!             E.M. (june 2009) use getin routine to load parameters
28!
29!
30!   arguments:
31!   ----------
32!
33!   input:
34!   ------
35!
36!    ngrid                 Size of the horizontal grid.
37!                          All internal loops are performed on that grid.
38!    nlayer                Number of vertical layers.
39!    pdayref               Day of reference for the simulation
40!    pday                  Number of days counted from the North. Spring
41!                          equinoxe.
42!
43!=======================================================================
44!
45!-----------------------------------------------------------------------
46!   declarations:
47!   -------------
48      use datafile_mod, only: datadir
49! to use  'getin'
50      USE ioipsl_getincom
51      IMPLICIT NONE
52#include "dimensions.h"
53#include "dimphys.h"
54#include "planete.h"
55#include "comcstfi.h"
56#include "callkeys.h"
57
58
59
60      REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
61 
62      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
63      REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
64      integer day_ini
65      INTEGER ig,ierr
66 
67      EXTERNAL iniorbit,orbite
68      EXTERNAL SSUM
69      REAL SSUM
70 
71      CHARACTER ch1*12
72      CHARACTER ch80*80
73
74      logical chem, h2o
75      logical :: parameter, doubleq=.false.
76
77      real psurf,pN2 ! added by RW for Gliese 581d N2+CO2
78
79      rad=prad
80      daysec=pdaysec
81      dtphys=ptimestep
82      cpp=pcpp
83      g=pg
84      r=pr
85      rcp=r/cpp
86
87      avocado = 6.02214179e23   ! added by RW
88
89! --------------------------------------------------------
90!     The usual Tests
91!     --------------
92      IF (nlayer.NE.nlayermx) THEN
93         PRINT*,'STOP in inifis'
94         PRINT*,'Probleme de dimensions :'
95         PRINT*,'nlayer     = ',nlayer
96         PRINT*,'nlayermx   = ',nlayermx
97         STOP
98      ENDIF
99
100      ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
101      ! (also done in dyn3d/defrun_new but not in LMDZ.COMMON)
102      call getin("ecritphy",ecritphy)
103
104! --------------------------------------------------------------
105!  Reading the "callphys.def" file controlling some key options
106! --------------------------------------------------------------
107     
108      ! check that 'callphys.def' file is around
109      OPEN(99,file='callphys.def',status='old',form='formatted'
110     &     ,iostat=ierr)
111      CLOSE(99)
112     
113      IF(ierr.EQ.0) THEN
114         PRINT*
115         PRINT*
116         PRINT*,'--------------------------------------------'
117         PRINT*,' inifis: Parametres pour la physique (callphys.def)'
118         PRINT*,'--------------------------------------------'
119
120         write(*,*) "Directory where external input files are:"
121         ! default 'datadir' is set in "datadir_mod"
122         call getin("datadir",datadir) ! default path
123         write(*,*) " datadir = ",trim(datadir)
124
125         write(*,*) "Run with or without tracer transport ?"
126         tracer=.false. ! default value
127         call getin("tracer",tracer)
128         write(*,*) " tracer = ",tracer
129
130         write(*,*) "Run with or without atm mass update ",
131     &      " due to tracer evaporation/condensation?"
132         mass_redistrib=.false. ! default value
133         call getin("mass_redistrib",mass_redistrib)
134         write(*,*) " mass_redistrib = ",mass_redistrib
135
136         write(*,*) "Diurnal cycle ?"
137         write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
138         diurnal=.true. ! default value
139         call getin("diurnal",diurnal)
140         write(*,*) " diurnal = ",diurnal
141
142         write(*,*) "Seasonal cycle ?"
143         write(*,*) "(if season=false, Ls stays constant, to value ",
144     &   "set in 'start'"
145         season=.true. ! default value
146         call getin("season",season)
147         write(*,*) " season = ",season
148
149         write(*,*) "Tidally resonant rotation ?"
150         tlocked=.false. ! default value
151         call getin("tlocked",tlocked)
152         write(*,*) "tlocked = ",tlocked
153
154         write(*,*) "Saturn ring shadowing ?"
155         rings_shadow = .false.
156         call getin("rings_shadow", rings_shadow)
157         write(*,*) "rings_shadow = ", rings_shadow
158         
159         write(*,*) "Compute latitude-dependent gravity field?"
160         oblate = .false.
161         call getin("oblate", oblate)
162         write(*,*) "oblate = ", oblate
163
164         write(*,*) "Flattening of the planet (a-b)/a "
165         flatten = 0.0
166         call getin("flatten", flatten)
167         write(*,*) "flatten = ", flatten
168         
169
170         write(*,*) "Needed if oblate=.true.: J2"
171         J2 = 0.0
172         call getin("J2", J2)
173         write(*,*) "J2 = ", J2
174         
175         write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
176         MassPlanet = 0.0
177         call getin("MassPlanet", MassPlanet)
178         write(*,*) "MassPlanet = ", MassPlanet         
179
180         write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
181         Rmean = 0.0
182         call getin("Rmean", Rmean)
183         write(*,*) "Rmean = ", Rmean
184         
185! Test of incompatibility:
186! if tlocked, then diurnal should be false
187         if (tlocked.and.diurnal) then
188           print*,'If diurnal=true, we should turn off tlocked.'
189           stop
190         endif
191
192         write(*,*) "Tidal resonance ratio ?"
193         nres=0          ! default value
194         call getin("nres",nres)
195         write(*,*) "nres = ",nres
196
197         write(*,*) "Write some extra output to the screen ?"
198         lwrite=.false. ! default value
199         call getin("lwrite",lwrite)
200         write(*,*) " lwrite = ",lwrite
201
202         write(*,*) "Save statistics in file stats.nc ?"
203         callstats=.true. ! default value
204         call getin("callstats",callstats)
205         write(*,*) " callstats = ",callstats
206
207         write(*,*) "Test energy conservation of model physics ?"
208         enertest=.false. ! default value
209         call getin("enertest",enertest)
210         write(*,*) " enertest = ",enertest
211
212         write(*,*) "Check to see if cpp values used match gases.def ?"
213         check_cpp_match=.true. ! default value
214         call getin("check_cpp_match",check_cpp_match)
215         write(*,*) " check_cpp_match = ",check_cpp_match
216
217         write(*,*) "call radiative transfer ?"
218         callrad=.true. ! default value
219         call getin("callrad",callrad)
220         write(*,*) " callrad = ",callrad
221
222         write(*,*) "call correlated-k radiative transfer ?"
223         corrk=.true. ! default value
224         call getin("corrk",corrk)
225         write(*,*) " corrk = ",corrk
226
227         write(*,*) "prohibit calculations outside corrk T grid?"
228         strictboundcorrk=.true. ! default value
229         call getin("strictboundcorrk",strictboundcorrk)
230         write(*,*) "strictboundcorrk = ",strictboundcorrk
231
232         write(*,*) "call gaseous absorption in the visible bands?",
233     &              "(matters only if callrad=T)"
234         callgasvis=.false. ! default value
235         call getin("callgasvis",callgasvis)
236         write(*,*) " callgasvis = ",callgasvis
237       
238         write(*,*) "call continuum opacities in radiative transfer ?",
239     &              "(matters only if callrad=T)"
240         continuum=.true. ! default value
241         call getin("continuum",continuum)
242         write(*,*) " continuum = ",continuum
243
244         write(*,*) "use analytic function for H2O continuum ?"
245         H2Ocont_simple=.false. ! default value
246         call getin("H2Ocont_simple",H2Ocont_simple)
247         write(*,*) " H2Ocont_simple = ",H2Ocont_simple
248 
249         write(*,*) "call turbulent vertical diffusion ?"
250         calldifv=.true. ! default value
251         call getin("calldifv",calldifv)
252         write(*,*) " calldifv = ",calldifv
253
254         write(*,*) "use turbdiff instead of vdifc ?"
255         UseTurbDiff=.true. ! default value
256         call getin("UseTurbDiff",UseTurbDiff)
257         write(*,*) " UseTurbDiff = ",UseTurbDiff
258
259         write(*,*) "call convective adjustment ?"
260         calladj=.true. ! default value
261         call getin("calladj",calladj)
262         write(*,*) " calladj = ",calladj
263
264         write(*,*) "call CO2 condensation ?"
265         co2cond=.false. ! default value
266         call getin("co2cond",co2cond)
267         write(*,*) " co2cond = ",co2cond
268! Test of incompatibility
269         if (co2cond.and.(.not.tracer)) then
270            print*,'We need a CO2 ice tracer to condense CO2'
271            call abort
272         endif
273 
274         write(*,*) "CO2 supersaturation level ?"
275         co2supsat=1.0 ! default value
276         call getin("co2supsat",co2supsat)
277         write(*,*) " co2supsat = ",co2supsat
278
279         write(*,*) "Radiative timescale for Newtonian cooling ?"
280         tau_relax=30. ! default value
281         call getin("tau_relax",tau_relax)
282         write(*,*) " tau_relax = ",tau_relax
283         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
284
285         write(*,*)"call thermal conduction in the soil ?"
286         callsoil=.true. ! default value
287         call getin("callsoil",callsoil)
288         write(*,*) " callsoil = ",callsoil
289         
290         write(*,*)"Rad transfer is computed every iradia",
291     &             " physical timestep"
292         iradia=1 ! default value
293         call getin("iradia",iradia)
294         write(*,*)" iradia = ",iradia
295       
296         write(*,*)"Rayleigh scattering ?"
297         rayleigh=.false.
298         call getin("rayleigh",rayleigh)
299         write(*,*)" rayleigh = ",rayleigh
300
301         write(*,*) "Use blackbody for stellar spectrum ?"
302         stelbbody=.false. ! default value
303         call getin("stelbbody",stelbbody)
304         write(*,*) " stelbbody = ",stelbbody
305
306         write(*,*) "Stellar blackbody temperature ?"
307         stelTbb=5800.0 ! default value
308         call getin("stelTbb",stelTbb)
309         write(*,*) " stelTbb = ",stelTbb
310
311         write(*,*)"Output mean OLR in 1D?"
312         meanOLR=.false.
313         call getin("meanOLR",meanOLR)
314         write(*,*)" meanOLR = ",meanOLR
315
316         write(*,*)"Output spectral OLR in 3D?"
317         specOLR=.false.
318         call getin("specOLR",specOLR)
319         write(*,*)" specOLR = ",specOLR
320
321         write(*,*)"Operate in kastprof mode?"
322         kastprof=.false.
323         call getin("kastprof",kastprof)
324         write(*,*)" kastprof = ",kastprof
325
326         write(*,*)"Uniform absorption in radiative transfer?"
327         graybody=.false.
328         call getin("graybody",graybody)
329         write(*,*)" graybody = ",graybody
330
331! Test of incompatibility:
332! if kastprof used, we must be in 1D
333         if (kastprof.and.(ngrid.gt.1)) then
334           print*,'kastprof can only be used in 1D!'
335           call abort
336         endif
337
338         write(*,*)"Stratospheric temperature for kastprof mode?"
339         Tstrat=167.0
340         call getin("Tstrat",Tstrat)
341         write(*,*)" Tstrat = ",Tstrat
342
343         write(*,*)"Remove lower boundary?"
344         nosurf=.false.
345         call getin("nosurf",nosurf)
346         write(*,*)" nosurf = ",nosurf
347
348! Tests of incompatibility:
349         if (nosurf.and.callsoil) then
350           print*,'nosurf not compatible with soil scheme!'
351           print*,'... got to make a choice!'
352           call abort
353         endif
354
355         write(*,*)"Add an internal heat flux?",
356     .             "... matters only if callsoil=F"
357         intheat=0.
358         call getin("intheat",intheat)
359         write(*,*)" intheat = ",intheat
360
361         write(*,*)"Use Newtonian cooling for radiative transfer?"
362         newtonian=.false.
363         call getin("newtonian",newtonian)
364         write(*,*)" newtonian = ",newtonian
365
366! Tests of incompatibility:
367         if (newtonian.and.corrk) then
368           print*,'newtonian not compatible with correlated-k!'
369           call abort
370         endif
371         if (newtonian.and.calladj) then
372           print*,'newtonian not compatible with adjustment!'
373           call abort
374         endif
375         if (newtonian.and.calldifv) then
376           print*,'newtonian not compatible with a boundary layer!'
377           call abort
378         endif
379
380         write(*,*)"Test physics timescale in 1D?"
381         testradtimes=.false.
382         call getin("testradtimes",testradtimes)
383         write(*,*)" testradtimes = ",testradtimes
384
385! Test of incompatibility:
386! if testradtimes used, we must be in 1D
387         if (testradtimes.and.(ngrid.gt.1)) then
388           print*,'testradtimes can only be used in 1D!'
389           call abort
390         endif
391
392         write(*,*)"Default planetary temperature?"
393         tplanet=215.0
394         call getin("tplanet",tplanet)
395         write(*,*)" tplanet = ",tplanet
396
397         write(*,*)"Which star?"
398         startype=1 ! default value = Sol
399         call getin("startype",startype)
400         write(*,*)" startype = ",startype
401
402         write(*,*)"Value of stellar flux at 1 AU?"
403         Fat1AU=1356.0 ! default value = Sol today
404         call getin("Fat1AU",Fat1AU)
405         write(*,*)" Fat1AU = ",Fat1AU
406
407
408! TRACERS:
409
410         write(*,*)"Varying H2O cloud fraction?"
411         CLFvarying=.false.     ! default value
412         call getin("CLFvarying",CLFvarying)
413         write(*,*)" CLFvarying = ",CLFvarying
414
415         write(*,*)"Value of fixed H2O cloud fraction?"
416         CLFfixval=1.0                ! default value
417         call getin("CLFfixval",CLFfixval)
418         write(*,*)" CLFfixval = ",CLFfixval
419
420         write(*,*)"fixed radii for Cloud particles?"
421         radfixed=.false. ! default value
422         call getin("radfixed",radfixed)
423         write(*,*)" radfixed = ",radfixed
424
425         if(kastprof)then
426            radfixed=.true.
427         endif 
428
429         write(*,*)"Number mixing ratio of CO2 ice particles:"
430         Nmix_co2=1.e6 ! default value
431         call getin("Nmix_co2",Nmix_co2)
432         write(*,*)" Nmix_co2 = ",Nmix_co2
433
434!         write(*,*)"Number of radiatively active aerosols:"
435!         naerkind=0. ! default value
436!         call getin("naerkind",naerkind)
437!         write(*,*)" naerkind = ",naerkind
438
439         write(*,*)"Opacity of dust (if used):"
440         dusttau=0. ! default value
441         call getin("dusttau",dusttau)
442         write(*,*)" dusttau = ",dusttau
443
444         write(*,*)"Radiatively active CO2 aerosols?"
445         aeroco2=.false.     ! default value
446         call getin("aeroco2",aeroco2)
447         write(*,*)" aeroco2 = ",aeroco2
448
449         write(*,*)"Fixed CO2 aerosol distribution?"
450         aerofixco2=.false.     ! default value
451         call getin("aerofixco2",aerofixco2)
452         write(*,*)" aerofixco2 = ",aerofixco2
453
454         write(*,*)"Radiatively active water ice?"
455         aeroh2o=.false.     ! default value
456         call getin("aeroh2o",aeroh2o)
457         write(*,*)" aeroh2o = ",aeroh2o
458
459         write(*,*)"Fixed H2O aerosol distribution?"
460         aerofixh2o=.false.     ! default value
461         call getin("aerofixh2o",aerofixh2o)
462         write(*,*)" aerofixh2o = ",aerofixh2o
463
464         write(*,*)"Radiatively active sulfuric acid aersols?"
465         aeroh2so4=.false.     ! default value
466         call getin("aeroh2so4",aeroh2so4)
467         write(*,*)" aeroh2so4 = ",aeroh2so4
468         
469!=================================
470
471         write(*,*)"Radiatively active two-layer aersols?"
472         aeroback2lay=.false.     ! default value
473         call getin("aeroback2lay",aeroback2lay)
474         write(*,*)" aeroback2lay = ",aeroback2lay
475
476         write(*,*)"TWOLAY AEROSOL: total optical depth ",
477     &              "in the tropospheric layer (visible)"
478         obs_tau_col_tropo=8.D0
479         call getin("obs_tau_col_tropo",obs_tau_col_tropo)
480         write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo
481
482         write(*,*)"TWOLAY AEROSOL: total optical depth ",
483     &              "in the stratospheric layer (visible)"
484         obs_tau_col_strato=0.08D0
485         call getin("obs_tau_col_strato",obs_tau_col_strato)
486         write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato
487
488         write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa"
489         pres_bottom_tropo=66000.0
490         call getin("pres_bottom_tropo",pres_bottom_tropo)
491         write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo
492
493         write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa"
494         pres_top_tropo=18000.0
495         call getin("pres_top_tropo",pres_top_tropo)
496         write(*,*)" pres_top_tropo = ",pres_top_tropo
497
498         write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa"
499         pres_bottom_strato=2000.0
500         call getin("pres_bottom_strato",pres_bottom_strato)
501         write(*,*)" pres_bottom_strato = ",pres_bottom_strato
502
503         write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa"
504         pres_top_strato=100.0
505         call getin("pres_top_strato",pres_top_strato)
506         write(*,*)" pres_top_strato = ",pres_top_strato
507
508         write(*,*)"TWOLAY AEROSOL: particle size in the ",
509     &              "tropospheric layer, in meters"
510         size_tropo=2.e-6
511         call getin("size_tropo",size_tropo)
512         write(*,*)" size_tropo = ",size_tropo
513
514         write(*,*)"TWOLAY AEROSOL: particle size in the ",
515     &              "stratospheric layer, in meters"
516         size_strato=1.e-7
517         call getin("size_strato",size_strato)
518         write(*,*)" size_strato = ",size_strato
519
520!=================================
521
522         write(*,*)"Cloud pressure level (with kastprof only):"
523         cloudlvl=0. ! default value
524         call getin("cloudlvl",cloudlvl)
525         write(*,*)" cloudlvl = ",cloudlvl
526
527         write(*,*)"Is the variable gas species radiatively active?"
528         Tstrat=167.0
529         varactive=.false.
530         call getin("varactive",varactive)
531         write(*,*)" varactive = ",varactive
532
533         write(*,*)"Is the variable gas species distribution set?"
534         varfixed=.false.
535         call getin("varfixed",varfixed)
536         write(*,*)" varfixed = ",varfixed
537
538         write(*,*)"What is the saturation % of the variable species?"
539         satval=0.8
540         call getin("satval",satval)
541         write(*,*)" satval = ",satval
542
543
544! Test of incompatibility:
545! if varactive, then varfixed should be false
546         if (varactive.and.varfixed) then
547           print*,'if varactive, varfixed must be OFF!'
548           stop
549         endif
550
551         write(*,*) "Gravitationnal sedimentation ?"
552         sedimentation=.false. ! default value
553         call getin("sedimentation",sedimentation)
554         write(*,*) " sedimentation = ",sedimentation
555
556         write(*,*) "Compute water cycle ?"
557         water=.false. ! default value
558         call getin("water",water)
559         write(*,*) " water = ",water
560         
561! Test of incompatibility:
562! if water is true, there should be at least a tracer
563         if (water.and.(.not.tracer)) then
564           print*,'if water is ON, tracer must be ON too!'
565           stop
566         endif
567
568         write(*,*) "Include water condensation ?"
569         watercond=.false. ! default value
570         call getin("watercond",watercond)
571         write(*,*) " watercond = ",watercond
572
573! Test of incompatibility:
574! if watercond is used, then water should be used too
575         if (watercond.and.(.not.water)) then
576           print*,'if watercond is used, water should be used too'
577           stop
578         endif
579
580         write(*,*) "Include water precipitation ?"
581         waterrain=.false. ! default value
582         call getin("waterrain",waterrain)
583         write(*,*) " waterrain = ",waterrain
584
585         write(*,*) "Include surface hydrology ?"
586         hydrology=.false. ! default value
587         call getin("hydrology",hydrology)
588         write(*,*) " hydrology = ",hydrology
589
590         write(*,*) "Evolve surface water sources ?"
591         sourceevol=.false. ! default value
592         call getin("sourceevol",sourceevol)
593         write(*,*) " sourceevol = ",sourceevol
594
595         write(*,*) "Ice evolution timestep ?"
596         icetstep=100.0 ! default value
597         call getin("icetstep",icetstep)
598         write(*,*) " icetstep = ",icetstep
599
600         write(*,*) "Snow albedo ?"
601         albedosnow=0.5         ! default value
602         call getin("albedosnow",albedosnow)
603         write(*,*) " albedosnow = ",albedosnow
604
605         write(*,*) "Maximum ice thickness ?"
606         maxicethick=2.0         ! default value
607         call getin("maxicethick",maxicethick)
608         write(*,*) " maxicethick = ",maxicethick
609
610         write(*,*) "Freezing point of seawater ?"
611         Tsaldiff=-1.8          ! default value
612         call getin("Tsaldiff",Tsaldiff)
613         write(*,*) " Tsaldiff = ",Tsaldiff
614
615         write(*,*) "Does user want to force cpp and mugaz?"
616         force_cpp=.false. ! default value
617         call getin("force_cpp",force_cpp)
618         write(*,*) " force_cpp = ",force_cpp
619
620         if (force_cpp) then
621           mugaz = -99999.
622           PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
623           call getin("mugaz",mugaz)
624           IF (mugaz.eq.-99999.) THEN
625               PRINT *, "mugaz must be set if force_cpp = T"
626               STOP
627           ELSE
628               write(*,*) "mugaz=",mugaz
629           ENDIF
630           cpp = -99999.
631           PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
632           call getin("cpp",cpp)
633           IF (cpp.eq.-99999.) THEN
634               PRINT *, "cpp must be set if force_cpp = T"
635               STOP
636           ELSE
637               write(*,*) "cpp=",cpp
638           ENDIF
639!         else
640!           mugaz=8.314*1000./pr
641         endif
642         call su_gases
643         call calc_cpp_mugaz
644
645         PRINT*,'--------------------------------------------'
646         PRINT*
647         PRINT*
648      ELSE
649         write(*,*)
650         write(*,*) 'Cannot read file callphys.def. Is it here ?'
651         stop
652      ENDIF
653
6548000  FORMAT(t5,a12,l8)
6558001  FORMAT(t5,a12,i8)
656
657      PRINT*
658      PRINT*,'inifis: daysec',daysec
659      PRINT*
660      PRINT*,'inifis: The radiative transfer is computed:'
661      PRINT*,'           each ',iradia,' physical time-step'
662      PRINT*,'        or each ',iradia*dtphys,' seconds'
663      PRINT*
664
665
666!-----------------------------------------------------------------------
667!     Some more initialization:
668!     ------------------------
669
670      ! ALLOCATE ARRAYS IN comgeomfi_h
671      IF (.not. ALLOCATED(lati)) ALLOCATE(lati(ngrid))
672      IF (.not. ALLOCATED(long)) ALLOCATE(long(ngrid))
673      IF (.not. ALLOCATED(area)) ALLOCATE(area(ngrid))
674
675      CALL SCOPY(ngrid,plon,1,long,1)
676      CALL SCOPY(ngrid,plat,1,lati,1)
677      CALL SCOPY(ngrid,parea,1,area,1)
678      totarea=SSUM(ngrid,area,1)
679
680      !! those are defined in comdiurn_h.F90
681      IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
682      IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
683      IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
684      IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
685
686      DO ig=1,ngrid
687         sinlat(ig)=sin(plat(ig))
688         coslat(ig)=cos(plat(ig))
689         sinlon(ig)=sin(plon(ig))
690         coslon(ig)=cos(plon(ig))
691      ENDDO
692
693      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
694
695      ! allocate "comsoil_h" arrays
696      call ini_comsoil_h(ngrid)
697     
698      END
Note: See TracBrowser for help on using the repository browser.