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

Last change on this file since 1202 was 1194, checked in by sglmd, 11 years ago

Latitude-dependent gravity field added. Option oblate = .true. in callphys.def, and three additional variables needed: J2, Rmean and MassPlanet?.

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