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

Last change on this file since 1157 was 1155, checked in by milmd, 11 years ago

LMDZ.GENERIC. sorry. previous commit (r1151) incuded a bug in inifis.F. forgot an elementary rule of fortran.

File size: 22.1 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! Test of incompatibility:
161! if tlocked, then diurnal should be false
162         if (tlocked.and.diurnal) then
163           print*,'If diurnal=true, we should turn off tlocked.'
164           stop
165         endif
166
167         write(*,*) "Tidal resonance ratio ?"
168         nres=0          ! default value
169         call getin("nres",nres)
170         write(*,*) "nres = ",nres
171
172         write(*,*) "Write some extra output to the screen ?"
173         lwrite=.false. ! default value
174         call getin("lwrite",lwrite)
175         write(*,*) " lwrite = ",lwrite
176
177         write(*,*) "Save statistics in file stats.nc ?"
178         callstats=.true. ! default value
179         call getin("callstats",callstats)
180         write(*,*) " callstats = ",callstats
181
182         write(*,*) "Test energy conservation of model physics ?"
183         enertest=.false. ! default value
184         call getin("enertest",enertest)
185         write(*,*) " enertest = ",enertest
186
187         write(*,*) "Check to see if cpp values used match gases.def ?"
188         check_cpp_match=.true. ! default value
189         call getin("check_cpp_match",check_cpp_match)
190         write(*,*) " check_cpp_match = ",check_cpp_match
191
192         write(*,*) "call radiative transfer ?"
193         callrad=.true. ! default value
194         call getin("callrad",callrad)
195         write(*,*) " callrad = ",callrad
196
197         write(*,*) "call correlated-k radiative transfer ?"
198         corrk=.true. ! default value
199         call getin("corrk",corrk)
200         write(*,*) " corrk = ",corrk
201
202         write(*,*) "prohibit calculations outside corrk T grid?"
203         strictboundcorrk=.true. ! default value
204         call getin("strictboundcorrk",strictboundcorrk)
205         write(*,*) "strictboundcorrk = ",strictboundcorrk
206
207         write(*,*) "call gaseous absorption in the visible bands?",
208     &              "(matters only if callrad=T)"
209         callgasvis=.false. ! default value
210         call getin("callgasvis",callgasvis)
211         write(*,*) " callgasvis = ",callgasvis
212       
213         write(*,*) "call continuum opacities in radiative transfer ?",
214     &              "(matters only if callrad=T)"
215         continuum=.true. ! default value
216         call getin("continuum",continuum)
217         write(*,*) " continuum = ",continuum
218
219         write(*,*) "use analytic function for H2O continuum ?"
220         H2Ocont_simple=.false. ! default value
221         call getin("H2Ocont_simple",H2Ocont_simple)
222         write(*,*) " H2Ocont_simple = ",H2Ocont_simple
223 
224         write(*,*) "call turbulent vertical diffusion ?"
225         calldifv=.true. ! default value
226         call getin("calldifv",calldifv)
227         write(*,*) " calldifv = ",calldifv
228
229         write(*,*) "use turbdiff instead of vdifc ?"
230         UseTurbDiff=.true. ! default value
231         call getin("UseTurbDiff",UseTurbDiff)
232         write(*,*) " UseTurbDiff = ",UseTurbDiff
233
234         write(*,*) "call convective adjustment ?"
235         calladj=.true. ! default value
236         call getin("calladj",calladj)
237         write(*,*) " calladj = ",calladj
238
239         write(*,*) "call CO2 condensation ?"
240         co2cond=.false. ! default value
241         call getin("co2cond",co2cond)
242         write(*,*) " co2cond = ",co2cond
243! Test of incompatibility
244         if (co2cond.and.(.not.tracer)) then
245            print*,'We need a CO2 ice tracer to condense CO2'
246            call abort
247         endif
248 
249         write(*,*) "CO2 supersaturation level ?"
250         co2supsat=1.0 ! default value
251         call getin("co2supsat",co2supsat)
252         write(*,*) " co2supsat = ",co2supsat
253
254         write(*,*) "Radiative timescale for Newtonian cooling ?"
255         tau_relax=30. ! default value
256         call getin("tau_relax",tau_relax)
257         write(*,*) " tau_relax = ",tau_relax
258         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
259
260         write(*,*)"call thermal conduction in the soil ?"
261         callsoil=.true. ! default value
262         call getin("callsoil",callsoil)
263         write(*,*) " callsoil = ",callsoil
264         
265         write(*,*)"Rad transfer is computed every iradia",
266     &             " physical timestep"
267         iradia=1 ! default value
268         call getin("iradia",iradia)
269         write(*,*)" iradia = ",iradia
270       
271         write(*,*)"Rayleigh scattering ?"
272         rayleigh=.false.
273         call getin("rayleigh",rayleigh)
274         write(*,*)" rayleigh = ",rayleigh
275
276         write(*,*) "Use blackbody for stellar spectrum ?"
277         stelbbody=.false. ! default value
278         call getin("stelbbody",stelbbody)
279         write(*,*) " stelbbody = ",stelbbody
280
281         write(*,*) "Stellar blackbody temperature ?"
282         stelTbb=5800.0 ! default value
283         call getin("stelTbb",stelTbb)
284         write(*,*) " stelTbb = ",stelTbb
285
286         write(*,*)"Output mean OLR in 1D?"
287         meanOLR=.false.
288         call getin("meanOLR",meanOLR)
289         write(*,*)" meanOLR = ",meanOLR
290
291         write(*,*)"Output spectral OLR in 3D?"
292         specOLR=.false.
293         call getin("specOLR",specOLR)
294         write(*,*)" specOLR = ",specOLR
295
296         write(*,*)"Operate in kastprof mode?"
297         kastprof=.false.
298         call getin("kastprof",kastprof)
299         write(*,*)" kastprof = ",kastprof
300
301         write(*,*)"Uniform absorption in radiative transfer?"
302         graybody=.false.
303         call getin("graybody",graybody)
304         write(*,*)" graybody = ",graybody
305
306! Test of incompatibility:
307! if kastprof used, we must be in 1D
308         if (kastprof.and.(ngrid.gt.1)) then
309           print*,'kastprof can only be used in 1D!'
310           call abort
311         endif
312
313         write(*,*)"Stratospheric temperature for kastprof mode?"
314         Tstrat=167.0
315         call getin("Tstrat",Tstrat)
316         write(*,*)" Tstrat = ",Tstrat
317
318         write(*,*)"Remove lower boundary?"
319         nosurf=.false.
320         call getin("nosurf",nosurf)
321         write(*,*)" nosurf = ",nosurf
322
323! Tests of incompatibility:
324         if (nosurf.and.callsoil) then
325           print*,'nosurf not compatible with soil scheme!'
326           print*,'... got to make a choice!'
327           call abort
328         endif
329
330         write(*,*)"Add an internal heat flux?",
331     .             "... matters only if callsoil=F"
332         intheat=0.
333         call getin("intheat",intheat)
334         write(*,*)" intheat = ",intheat
335
336         write(*,*)"Use Newtonian cooling for radiative transfer?"
337         newtonian=.false.
338         call getin("newtonian",newtonian)
339         write(*,*)" newtonian = ",newtonian
340
341! Tests of incompatibility:
342         if (newtonian.and.corrk) then
343           print*,'newtonian not compatible with correlated-k!'
344           call abort
345         endif
346         if (newtonian.and.calladj) then
347           print*,'newtonian not compatible with adjustment!'
348           call abort
349         endif
350         if (newtonian.and.calldifv) then
351           print*,'newtonian not compatible with a boundary layer!'
352           call abort
353         endif
354
355         write(*,*)"Test physics timescale in 1D?"
356         testradtimes=.false.
357         call getin("testradtimes",testradtimes)
358         write(*,*)" testradtimes = ",testradtimes
359
360! Test of incompatibility:
361! if testradtimes used, we must be in 1D
362         if (testradtimes.and.(ngrid.gt.1)) then
363           print*,'testradtimes can only be used in 1D!'
364           call abort
365         endif
366
367         write(*,*)"Default planetary temperature?"
368         tplanet=215.0
369         call getin("tplanet",tplanet)
370         write(*,*)" tplanet = ",tplanet
371
372         write(*,*)"Which star?"
373         startype=1 ! default value = Sol
374         call getin("startype",startype)
375         write(*,*)" startype = ",startype
376
377         write(*,*)"Value of stellar flux at 1 AU?"
378         Fat1AU=1356.0 ! default value = Sol today
379         call getin("Fat1AU",Fat1AU)
380         write(*,*)" Fat1AU = ",Fat1AU
381
382
383! TRACERS:
384
385         write(*,*)"Varying H2O cloud fraction?"
386         CLFvarying=.false.     ! default value
387         call getin("CLFvarying",CLFvarying)
388         write(*,*)" CLFvarying = ",CLFvarying
389
390         write(*,*)"Value of fixed H2O cloud fraction?"
391         CLFfixval=1.0                ! default value
392         call getin("CLFfixval",CLFfixval)
393         write(*,*)" CLFfixval = ",CLFfixval
394
395         write(*,*)"fixed radii for Cloud particles?"
396         radfixed=.false. ! default value
397         call getin("radfixed",radfixed)
398         write(*,*)" radfixed = ",radfixed
399
400         if(kastprof)then
401            radfixed=.true.
402         endif 
403
404         write(*,*)"Number mixing ratio of CO2 ice particles:"
405         Nmix_co2=1.e6 ! default value
406         call getin("Nmix_co2",Nmix_co2)
407         write(*,*)" Nmix_co2 = ",Nmix_co2
408
409!         write(*,*)"Number of radiatively active aerosols:"
410!         naerkind=0. ! default value
411!         call getin("naerkind",naerkind)
412!         write(*,*)" naerkind = ",naerkind
413
414         write(*,*)"Opacity of dust (if used):"
415         dusttau=0. ! default value
416         call getin("dusttau",dusttau)
417         write(*,*)" dusttau = ",dusttau
418
419         write(*,*)"Radiatively active CO2 aerosols?"
420         aeroco2=.false.     ! default value
421         call getin("aeroco2",aeroco2)
422         write(*,*)" aeroco2 = ",aeroco2
423
424         write(*,*)"Fixed CO2 aerosol distribution?"
425         aerofixco2=.false.     ! default value
426         call getin("aerofixco2",aerofixco2)
427         write(*,*)" aerofixco2 = ",aerofixco2
428
429         write(*,*)"Radiatively active water ice?"
430         aeroh2o=.false.     ! default value
431         call getin("aeroh2o",aeroh2o)
432         write(*,*)" aeroh2o = ",aeroh2o
433
434         write(*,*)"Fixed H2O aerosol distribution?"
435         aerofixh2o=.false.     ! default value
436         call getin("aerofixh2o",aerofixh2o)
437         write(*,*)" aerofixh2o = ",aerofixh2o
438
439         write(*,*)"Radiatively active sulfuric acid aersols?"
440         aeroh2so4=.false.     ! default value
441         call getin("aeroh2so4",aeroh2so4)
442         write(*,*)" aeroh2so4 = ",aeroh2so4
443         
444!=================================
445
446         write(*,*)"Radiatively active two-layer aersols?"
447         aeroback2lay=.false.     ! default value
448         call getin("aeroback2lay",aeroback2lay)
449         write(*,*)" aeroback2lay = ",aeroback2lay
450
451         write(*,*)"TWOLAY AEROSOL: total optical depth ",
452     &              "in the tropospheric layer (visible)"
453         obs_tau_col_tropo=8.D0
454         call getin("obs_tau_col_tropo",obs_tau_col_tropo)
455         write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo
456
457         write(*,*)"TWOLAY AEROSOL: total optical depth ",
458     &              "in the stratospheric layer (visible)"
459         obs_tau_col_strato=0.08D0
460         call getin("obs_tau_col_strato",obs_tau_col_strato)
461         write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato
462
463         write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa"
464         pres_bottom_tropo=66000.0
465         call getin("pres_bottom_tropo",pres_bottom_tropo)
466         write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo
467
468         write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa"
469         pres_top_tropo=18000.0
470         call getin("pres_top_tropo",pres_top_tropo)
471         write(*,*)" pres_top_tropo = ",pres_top_tropo
472
473         write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa"
474         pres_bottom_strato=2000.0
475         call getin("pres_bottom_strato",pres_bottom_strato)
476         write(*,*)" pres_bottom_strato = ",pres_bottom_strato
477
478         write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa"
479         pres_top_strato=100.0
480         call getin("pres_top_strato",pres_top_strato)
481         write(*,*)" pres_top_strato = ",pres_top_strato
482
483         write(*,*)"TWOLAY AEROSOL: particle size in the ",
484     &              "tropospheric layer, in meters"
485         size_tropo=2.e-6
486         call getin("size_tropo",size_tropo)
487         write(*,*)" size_tropo = ",size_tropo
488
489         write(*,*)"TWOLAY AEROSOL: particle size in the ",
490     &              "stratospheric layer, in meters"
491         size_strato=1.e-7
492         call getin("size_strato",size_strato)
493         write(*,*)" size_strato = ",size_strato
494
495!=================================
496
497         write(*,*)"Cloud pressure level (with kastprof only):"
498         cloudlvl=0. ! default value
499         call getin("cloudlvl",cloudlvl)
500         write(*,*)" cloudlvl = ",cloudlvl
501
502         write(*,*)"Is the variable gas species radiatively active?"
503         Tstrat=167.0
504         varactive=.false.
505         call getin("varactive",varactive)
506         write(*,*)" varactive = ",varactive
507
508         write(*,*)"Is the variable gas species distribution set?"
509         varfixed=.false.
510         call getin("varfixed",varfixed)
511         write(*,*)" varfixed = ",varfixed
512
513         write(*,*)"What is the saturation % of the variable species?"
514         satval=0.8
515         call getin("satval",satval)
516         write(*,*)" satval = ",satval
517
518
519! Test of incompatibility:
520! if varactive, then varfixed should be false
521         if (varactive.and.varfixed) then
522           print*,'if varactive, varfixed must be OFF!'
523           stop
524         endif
525
526         write(*,*) "Gravitationnal sedimentation ?"
527         sedimentation=.false. ! default value
528         call getin("sedimentation",sedimentation)
529         write(*,*) " sedimentation = ",sedimentation
530
531         write(*,*) "Compute water cycle ?"
532         water=.false. ! default value
533         call getin("water",water)
534         write(*,*) " water = ",water
535         
536! Test of incompatibility:
537! if water is true, there should be at least a tracer
538         if (water.and.(.not.tracer)) then
539           print*,'if water is ON, tracer must be ON too!'
540           stop
541         endif
542
543         write(*,*) "Include water condensation ?"
544         watercond=.false. ! default value
545         call getin("watercond",watercond)
546         write(*,*) " watercond = ",watercond
547
548! Test of incompatibility:
549! if watercond is used, then water should be used too
550         if (watercond.and.(.not.water)) then
551           print*,'if watercond is used, water should be used too'
552           stop
553         endif
554
555         write(*,*) "Include water precipitation ?"
556         waterrain=.false. ! default value
557         call getin("waterrain",waterrain)
558         write(*,*) " waterrain = ",waterrain
559
560         write(*,*) "Include surface hydrology ?"
561         hydrology=.false. ! default value
562         call getin("hydrology",hydrology)
563         write(*,*) " hydrology = ",hydrology
564
565         write(*,*) "Evolve surface water sources ?"
566         sourceevol=.false. ! default value
567         call getin("sourceevol",sourceevol)
568         write(*,*) " sourceevol = ",sourceevol
569
570         write(*,*) "Ice evolution timestep ?"
571         icetstep=100.0 ! default value
572         call getin("icetstep",icetstep)
573         write(*,*) " icetstep = ",icetstep
574
575         write(*,*) "Snow albedo ?"
576         albedosnow=0.5         ! default value
577         call getin("albedosnow",albedosnow)
578         write(*,*) " albedosnow = ",albedosnow
579
580         write(*,*) "Maximum ice thickness ?"
581         maxicethick=2.0         ! default value
582         call getin("maxicethick",maxicethick)
583         write(*,*) " maxicethick = ",maxicethick
584
585         write(*,*) "Freezing point of seawater ?"
586         Tsaldiff=-1.8          ! default value
587         call getin("Tsaldiff",Tsaldiff)
588         write(*,*) " Tsaldiff = ",Tsaldiff
589
590         write(*,*) "Does user want to force cpp and mugaz?"
591         force_cpp=.false. ! default value
592         call getin("force_cpp",force_cpp)
593         write(*,*) " force_cpp = ",force_cpp
594
595         if (force_cpp) then
596           mugaz = -99999.
597           PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
598           call getin("mugaz",mugaz)
599           IF (mugaz.eq.-99999.) THEN
600               PRINT *, "mugaz must be set if force_cpp = T"
601               STOP
602           ELSE
603               write(*,*) "mugaz=",mugaz
604           ENDIF
605           cpp = -99999.
606           PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
607           call getin("cpp",cpp)
608           IF (cpp.eq.-99999.) THEN
609               PRINT *, "cpp must be set if force_cpp = T"
610               STOP
611           ELSE
612               write(*,*) "cpp=",cpp
613           ENDIF
614!         else
615!           mugaz=8.314*1000./pr
616         endif
617         call su_gases
618         call calc_cpp_mugaz
619
620         PRINT*,'--------------------------------------------'
621         PRINT*
622         PRINT*
623      ELSE
624         write(*,*)
625         write(*,*) 'Cannot read file callphys.def. Is it here ?'
626         stop
627      ENDIF
628
6298000  FORMAT(t5,a12,l8)
6308001  FORMAT(t5,a12,i8)
631
632      PRINT*
633      PRINT*,'inifis: daysec',daysec
634      PRINT*
635      PRINT*,'inifis: The radiative transfer is computed:'
636      PRINT*,'           each ',iradia,' physical time-step'
637      PRINT*,'        or each ',iradia*dtphys,' seconds'
638      PRINT*
639
640
641!-----------------------------------------------------------------------
642!     Some more initialization:
643!     ------------------------
644
645      ! ALLOCATE ARRAYS IN comgeomfi_h
646      IF (.not. ALLOCATED(lati)) ALLOCATE(lati(ngrid))
647      IF (.not. ALLOCATED(long)) ALLOCATE(long(ngrid))
648      IF (.not. ALLOCATED(area)) ALLOCATE(area(ngrid))
649
650      CALL SCOPY(ngrid,plon,1,long,1)
651      CALL SCOPY(ngrid,plat,1,lati,1)
652      CALL SCOPY(ngrid,parea,1,area,1)
653      totarea=SSUM(ngrid,area,1)
654
655      !! those are defined in comdiurn_h.F90
656      IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
657      IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
658      IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
659      IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
660
661      DO ig=1,ngrid
662         sinlat(ig)=sin(plat(ig))
663         coslat(ig)=cos(plat(ig))
664         sinlon(ig)=sin(plon(ig))
665         coslon(ig)=cos(plon(ig))
666      ENDDO
667
668      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
669
670      RETURN
671      END
Note: See TracBrowser for help on using the repository browser.